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


RE: The future of Haskell discussion

2001-09-17 Thread Simon Marlow

Jeffrey Palmer writes:
 I think the question is more along the lines of Why doesn't Haskell
 come bundled with complete, useful and _supported_ libraries?

There's an ongoing effort to rectify the situation.  There is a mailing
list: [EMAIL PROTECTED], which you can join by going to 

http://www.haskell.org/mailman/listinfo/libraries

(there are archives of previous discussion there too).  A draft document
describes the current plan:

http://www.haskell.org/~simonmar/libraries/libraries.html

and what source code we have so far is in CVS:

http://cvs.haskell.org/cgi-bin/cvsweb.cgi/fptools/libraries/

Cheers,
Simon

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



Re: The future of Haskell discussion

2001-09-17 Thread Yoann Padioleau

Alastair David Reid [EMAIL PROTECTED] writes:

 In the case of the Draw monad (which is identical to the
 IO monad except that it carries a device context around as an
 implicit parameter), the different feel comes from aggressive
 use of continuations (actually, they're not quite continuations
 but I don't have a better word for them).  For example, you might
 normally write code like this:
 
   do
 old_color - selectColor blue
 old_font  - selectFont  helvetica
 write_text Hello World
 selectFont  old_font
 selectColor old_color
 
 (Reselecting the old color and font at the end is recommended Win32
 programming style.)
 
 In the HGL, you instead write:
 
   setPicture window (withColor blue (withFont helvetica (text Hello World)))

you can achieve the same in many langage such as c++. 
I dont really see what is haskell specific in your code.

pseudo code (i dont remember exactly c++ :) ):

class Draw {
 Color color;
 Font  font;
 Widget wid;
 
 Draw(Widget w) { wid = w }
 draw(window) { Color old; Font old;  
oldc = setColor color; oldf = setFont font; 
wid.draw(window);
setColor oldc; setFont oldf;
   }  
 withColor (Color c) {color = c}
 withFont  (Font f)  {font = f}
}

new Draw(new textWidget(Hello 
World))-withColor(blue)-withFont(helvetica)-draw(window)
   
there are plenty of way to achieve what you do.

 
 or, equivalently but allegedly easier to read,
 
   setPicture window$
 withColor blue $
 withFont helvetica $
 text Hello World
 
 where withColor and withFont are defined like this:
 
   withColor :: Color - Draw a - Draw a
   withColor c m = do{ old - selectColor c; a - m; selectColor old; return a }
 
   withFont  :: Font  - Draw a - Draw a
   withFont f m = do{ old - selectFont f; a - m; selectFont old; return a }
 
 and setPicture exploits the fact that an object of type Draw a is a
 first class object which can be stored in the window state and
 executed when appropriate (e.g., when the window is uniconified).
 
 
 What I'm saying is that Haskell's standard abstraction facilities mean
 that even in the IO monad your programming experience can
 significantly better than that of a C programmer.  (Of course your
 experience can also be worse if you don't or can't bring Haskell's
 strengths to bear on your problem.)

-- 
Yoann  Padioleau,  INSA de Rennes, France,   http://www.irisa.fr/prive/padiolea
Opinions expressed here are only mine. Je n'écris qu'à titre personnel.
**   Get Free. Be Smart.  Simply use Linux and Free Software.   **

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



Re: The future of Haskell discussion / GUIs

2001-09-15 Thread Manuel M. T. Chakravarty

Johannes Waldmann [EMAIL PROTECTED] wrote,

 Manuel:
 
  ... Functional GUIs like
  Fruit are from a research perspective very interesting, but
  their design is rather far from being a solved problem,
  which makes them a not very likely candidate for a standard
  that people seem to like to have sooner rather than later.
 
 just to voice a slightly differnt opinion: 
 I worked with FranTk a bit and found it quite easy to handle.
 There are some technical problems maybe,
 but they do not come from the design but rather from using Tcl/Tk.
 The design itself is rather abstract (that's the very intention),
 and is not tied to one particular backend.

Hmm, I didn't mention FranTk in the cited paragraph.  Fruit
and FranTk are rather different.

Manuel

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



Re: The future of Haskell discussion

2001-09-15 Thread Manuel M. T. Chakravarty

S. Alexander Jacobson [EMAIL PROTECTED] wrote,

 If the GUI is based on the IO monad, then it doesn't seem like there is
 a lot of advantage  to doing it in Haskell.  It seems like a better
 idea to use a more natural language for IO and make RPC/interproc calls
 to a haskell server to get stuff done.

I completely disagree - with SimonPJ's words (I think from
the Awkward Squad paper), ``Haskell is the world's finest
imperative programming language.''

Side effects are one thing, but having Haskell type system
and support for higher-order functions available makes
imperative programming so much nice.  For example, proper
support for closures makes the whole signal handling code
needed for GTK+-based GUIs much nicer in Haskell than in C.

And this is not just idle theory.  Most of the code in
Gtk+HS lives in the IO monad and and it's a considerable
amount of code.  I came to the stated opinion after having
written that.

Cheers,
Manuel

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



Re: The future of Haskell discussion

2001-09-15 Thread Bill Halchin


Jeff has hit the nail on the head .. thanks Jeff. You said eloquentlywhat I was hinting at
or saying very implicit (because I didn't know how to say it eloquently). The "Haskell
library" seems to be contributions by individuals (who should be commended!!), butas
an "industrial" programmer who writes in imperative languages everyday (and sees
them as many times getting in the way, e.g. C++,and not modelinga particular
problem very elegantly!), with Haskell I would like to see a library API part of the
Haskell Report, i.e. a nice list of type signatures by topic, e.g. numeric. (maybe this
is already the situation ... I unfortunately have not had a lot of chance to write 
Haskel code even though I like FPL's and Haskell in particular). The haskell library API
should be part of the Haskell standard just as the standard C library is part of the 
ANSI C standard!
Regards, Bill Halchin

From: Jeffrey Palmer <[EMAIL PROTECTED]>
To: [EMAIL PROTECTED] 
Subject: Re: The future of Haskell discussion 
Date: 14 Sep 2001 17:06:49 -0500 
 
On Fri, 2001-09-14 at 15:12, Mark Carroll wrote: 
  On Fri, 14 Sep 2001, Bill Halchin wrote: 
  
   Probably this question has been brought before. Besides the Preludes, 
   why doesn't 
   
   Haskell have libraries like Java, Squeak (Smalltalk). I found this: 
  (snip) 
  
  I'm puzzled - it does! - see http://www.haskell.org/libraries/ for some of 
  them. 
  
 
I think the question is more along the lines of "Why doesn't Haskell 
come bundled with complete, useful and _supported_ libraries?" 
 
For example, the Edison home page describes the library in this way: 
 
"in its current state, the library is mostly a framework. That is, I 
provide signatures, but not yet very many implementations..." 
 
This is not the type of thing that your standard software engineer wants 
to hear. Professional software developers need to be highly productive, 
and are often unwilling to invest time learning libraries that aren't 
part of the core language environment. However you feel about the 
design of the Java Collections API, at least it's a supported part of 
the language. Developers feel comfortable that any time spent learning 
the how to use these APIs is worthwhile. 
 
I felt this very recently when looking for a quality GUI framework for 
Haskell. There appear to be many(!) libraries available, and all seem 
to be in various states of completion. Personally, I would like to see 
someone complete the port of the Clean library that was attempted, as 
that library seems to have been pretty battle-tested, and there are lots 
of good, real-world examples. 
 
That, I suppose, is the key point. Whatever libraries are chosen for 
final inclusion in the Haskell environment, they should be treated as 
integral to the language experience. Extensive documentation and 
examples should exist, perhaps of book length (I really liked Hudak's 
text for this reason, and only wish that it had been written with the 
"standard" Haskell GUI libs). Finally, any libraries should be beaten 
upon to such an extent that there is a solid guarantee that they are 
"safe" for production use. 
 
Thoughts? 
 
 - j 
 
 
-- 
Jeffrey Palmer 
Curious Networks, Inc. 
http://www.curiousnetworks.com 
e: [EMAIL PROTECTED] 
 
 
___ 
Haskell mailing list 
[EMAIL PROTECTED] 
http://www.haskell.org/mailman/listinfo/haskell 
Get your FREE download of MSN Explorer at http://explorer.msn.com

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


Re: The future of Haskell discussion

2001-09-15 Thread Pixel

Marcin 'Qrczak' Kowalczyk [EMAIL PROTECTED] writes:

 Fri, 14 Sep 2001 02:09:21 -0700, Julian Seward (Intl Vendor) 
[EMAIL PROTECTED] pisze:
 
  The lack of any way to interface to C++ is a problem, IMO.
  I would love to be able to write Haskell programs using Qt
  and ultimately the KDE libraries, both of which are C++, but
  I can't, at the mo.
 
 I think it should be easy to add support for C++, except exceptions.

for info, Qt/KDE do not use exceptions and compile with -fno-exceptions

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



Re: The future of Haskell discussion

2001-09-14 Thread Wolfgang Jeltsch

On Friday, 14. September 2001 04:38, you wrote:
 [...]
 wxWindows is quite C++ centric and AFAIK nobody has made a
 serious effort at a C++ FFI yet.  One of the big advantages
 of GTK+ is that it was written with bindings for other
 languages in mind.  Therefore, it is probably the toolkit
 with the most language bindings.

I didn't mean that a Haskell binding to wxWindows should be made. I meant 
that the strategy of wxWindows should be used also for a Haskell GUI library. 
This strategy is to define a common GUI interface and provide implementations 
for different platforms based on different libraries like GTK+ (for GNOME), 
Qt (for KDE), Win32.
By the way a Haskell binding to wxWindows would maybe cause performance 
problems just because wxWindows isn't native but itself uses other GUI 
libraries.

Wolfgang

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



Re: The future of Haskell discussion

2001-09-14 Thread Johannes Waldmann


 As such, I would like to see a focus on making Haskell great for web
 application and web service development.  

Right. On the server side, this is easy (and people have done it,
see the example HTML server, and I've used it to code up a game server,
used for a students' programming contest here (*)).

I would love to see Haskell used on the client side, that is, 
I want Haskell applets. This would probably require that the user
downloads Hugs as a netscape-plugin?  Or ghc emits Java (byte-)code?
And in both cases: what GUI should we use?

In case you wonder - this application is purely academic:
the applets should help my students to understands certain concepts
in theoretical computer science. Of course I would then welcome 
their questions on how did you program this...

(for an example, see the PCP Puzzle
http://www.informatik.uni-leipzig.de/~pcp/ but that is a Java program.
I want to program exactly this kind of applet in Haskell!)


(*) the server itself runs fine, but the Java applet to play/display games
http://theopc.informatik.uni-leipzig.de/~connect/  currently is broken :-)
-- 
-- Johannes Waldmann  http://www.informatik.uni-leipzig.de/~joe/ --
-- [EMAIL PROTECTED] -- phone/fax (+49) 341 9732 204/252 --

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



Re: The future of Haskell discussion

2001-09-14 Thread Rijk-Jan van Haaften


I would love to see Haskell used on the client side, that is,
I want Haskell applets.

I know of one Haskell applet running on the internet.

This would probably require that the user
downloads Hugs as a netscape-plugin?  Or ghc emits Java (byte-)code?
And in both cases: what GUI should we use?

There are proposals for java byte-code backends for ghc. However, there
are currently no concrete products implementing such a backend. I know
three links to papers in this area, the last one coming with a Haskell applet
example.

D. Wakeling wrote three papers which are available at
http://www.dcs.ex.ac.uk/~david/en/research/previous/java/

Martijn de Vries wrote a paper which is at
http://www.i2x.com/~martijn/

Alessandro Vernet wrote an article and a backend, but he mailed me
he lost the backend due to a computer crash.
http://www.scdi.org/~avernet/projects/jaskell/
Still, he has one haskell-applet (having the algorithm written in Haskell
and the GUI written in Java) which survived the crash. It is running at
http://www.scdi.org/~avernet/projects/jaskell/queens/

Rijk-Jan


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



RE: The future of Haskell discussion

2001-09-14 Thread Julian Seward (Intl Vendor)


| wxWindows is quite C++ centric and AFAIK nobody has made a 
| serious effort at a C++ FFI yet.  One of the big advantages 
| of GTK+ is that it was written with bindings for other 
| languages in mind.  Therefore, it is probably the toolkit 
| with the most language bindings.

The lack of any way to interface to C++ is a problem, IMO.
I would love to be able to write Haskell programs using Qt
and ultimately the KDE libraries, both of which are C++, but
I can't, at the mo.

J

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



Re: The future of Haskell discussion

2001-09-14 Thread Marcin 'Qrczak' Kowalczyk

Fri, 14 Sep 2001 02:09:21 -0700, Julian Seward (Intl Vendor) [EMAIL PROTECTED] 
pisze:

 The lack of any way to interface to C++ is a problem, IMO.
 I would love to be able to write Haskell programs using Qt
 and ultimately the KDE libraries, both of which are C++, but
 I can't, at the mo.

I think it should be easy to add support for C++, except exceptions.

There are two approaches: call C++ functions directly (it requires
implementing name mangling by the Haskell compiler; there are several
name mangling schemes and gcc changed its scheme in version 3.0)
or write C wrappers (this is inconvenient but is doable now without
compiler support).

An annoyance is that templates can't be called directly but each
instance must be imported separately.

On Linux it works when main() of a mixed C/C++ program is written in C.
AFAIK it doesn't work everywhere. Nevertheless an example I've now
made worked.

hsc2hs and ghc need to be extended to make it work smoothly. hsc2hs
produces a file with extension .c and ghc compiles these files by
passing -x c options to the C compiler, so even if a C++ compiler is
substituted, it is compiled as C. There should be a switch in hsc2hs
to let it produce C++ and ghc should recognize .cc extension, or
in some other way ghc should be informed that the .c file is really
C++. Option -pgmlg++ causes ghc to link using g++; option -lstdc++
instead also works. And hsc2hs should be taught about extern C.

-- 
 __(  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: The future of Haskell discussion

2001-09-14 Thread D. Tweed

As a general question (and forgive my ignorance): are the various ffi's
implemented using something like `dlopen' or are they done by actually
putting suitable stubs into the Haskell generated C-code which then gets
compiled by the C compiler as part of the overall haskell compilation?

On 14 Sep 2001, Marcin 'Qrczak' Kowalczyk wrote:

 I think it should be easy to add support for C++, except exceptions.
 
 There are two approaches: call C++ functions directly (it requires
 implementing name mangling by the Haskell compiler; there are several
 name mangling schemes and gcc changed its scheme in version 3.0)
 or write C wrappers (this is inconvenient but is doable now without
 compiler support).

I suspect that there's several different levels of C++ interface; here's
mty personal taxonomy (which other people may disagree with :-) ) :

(1) Firstly there's calling code where the interface is basically C but
compiled with
C++; at this level there's the issue of name mangling (accounting for both
for argument structure and namespace effects) and any global stuff
in the C++ code (e.g., ensuring global objects construction/destruction
happens at times that are ok).

(2) Then there's being able to invoke the method of an object without
caring about moving `inside object' information back in to haskell (e.g.,
calling the colour_segment() member of an object of the Image class). Here
the object is essentially just acting as a `struct with attatched function
pointers'.

(3) Then there's being able to actually use objects more fully via a
Haskell type/type-class wrapper of some sort (so that for example objects
of C++-class X_cpp with a member function

string show(void) const

could be used in, e.g,

display :: [X_haskell] - IO()
display = sequence (map (putStr.show))

Obviously this throws up issues of the semantics that need to be solved
(e.g., can I only use const member functions, or can I use them all
providing I embed the object in a monad?) and is (I imagine) a heavy
research and implementation project.

(4) Finally there's being able to propagate C++ exceptions into Haskell,
using either Haskell exceptions or some other representation. (This is
clearly incredibly hard, but I belive some package (forget which) manages
to propagate C++ exceptions into Python exceptions.)

From my limited understanding, the really nice bits about the KDE
framework (e.g., embedding application objects inside others) would
require at least level (3) and possibly even (4).

 An annoyance is that templates can't be called directly but each
 instance must be imported separately.

Indeed, with a potential additional problem: many template functions are
written as inlines in header files, so that if I try and use a template
function I wrote years ago in a .cc file containing a C++ class I defined
yesterday I silently get the correct code compiled into the new .o
file. If I try to `glue' together a template function and a new C++ type
(where they haven't been used together otherwise) where does the new
instantiation go; do I have to go around adding explicit instatantiation
requests in the C++ source?

 On Linux it works when main() of a mixed C/C++ program is written in C.
 AFAIK it doesn't work everywhere. Nevertheless an example I've now
 made worked.
 
 hsc2hs and ghc need to be extended to make it work smoothly. hsc2hs
 produces a file with extension .c and ghc compiles these files by
 passing -x c options to the C compiler, so even if a C++ compiler is
 substituted, it is compiled as C. There should be a switch in hsc2hs
 to let it produce C++ and ghc should recognize .cc extension, or
 in some other way ghc should be informed that the .c file is really
 C++. Option -pgmlg++ causes ghc to link using g++; option -lstdc++
 instead also works. And hsc2hs should be taught about extern C.

All these are useful things; however I'm just pointing out that there's
various degrees of interoperation with C++. My personal position at the
moment is that I want to be able to use the level 1 facilities above with
minimal effort (and to be able to call in to Haskell from C++, but that's
another story) for program development purposes. If there's
any coding that better informed people can suggest to make
interfacing with C++ easier I can try and help with it, but unfortunately
(1) I'm unreliable; (2) I can't justify doing development on interfacing
C++-Haskell as part of my job so it'd only be during my very scarce free
time; (3) did I mention I'm incredibly unreliable? 

___cheers,_dave
www.cs.bris.ac.uk/~tweed/pi.htm |tweed's law:  however many computers
email: [EMAIL PROTECTED]  |   you have, half your time is spent
work tel: (0117) 954-5250   |   waiting for compilations to finish.


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



Re: The future of Haskell discussion

2001-09-14 Thread Manuel M. T. Chakravarty

S. Alexander Jacobson [EMAIL PROTECTED] wrote,

 Out of curiosity, how does GTK+ compare with Fruit?

GTK+ has a C API heavily based on call backs and mutable
state.  Thus, the Haskell transcription of that API heavily
relies on the use of the IO monad - as does H98 textual IO.

 It seems like it would make sense for the standard Haskell GUI also to be
 functional.

A functional GUI would be nice, but standard Haskell text
and file I/O is not functional either.  Functional GUIs like
Fruit are from a research perspective very interesting, but
their design is rather far from being a solved problem,
which makes them a not very likely candidate for a standard
that people seem to like to have sooner rather than later.

Cheers,
Manuel


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



Re: The future of Haskell discussion

2001-09-14 Thread Manuel M. T. Chakravarty

Mark Carroll [EMAIL PROTECTED] wrote,

 On Fri, 14 Sep 2001, Manuel M. T. Chakravarty wrote:
 (snip)
  wxWindows is quite C++ centric and AFAIK nobody has made a
  serious effort at a C++ FFI yet.  One of the big advantages
 (snip)
 
 Of course, wxPython also exists - I assume that the emphasis on object
 orientation is the problem?

Also, the lack of a static type system makes it easier to
embed foreign APIs into Python.

Manuel

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



Re: The future of Haskell discussion

2001-09-14 Thread Peter Achten

At 09:58 14-9-01 +0200, Wolfgang Jeltsch wrote:

I didn't mean that a Haskell binding to wxWindows should be made. I meant
that the strategy of wxWindows should be used also for a Haskell GUI library.
This strategy is to define a common GUI interface and provide implementations
for different platforms based on different libraries like GTK+ (for GNOME),
Qt (for KDE), Win32.

This strategy has been followed by the pilot project that has been 
described in [1]. In this project we have ported a crucial subset of the 
Clean Object I/O library to Haskell. The Clean Object I/O library is used 
for major projects such as the Clean IDE and the Clean theorem prover 
SPARKLE by Maarten de Mol.
The pilot port has been done on a Windows platform, so that we could reuse 
the primitive implementation layer. To port it to a more Unix friendly 
environment, I guess Manuel Chakravarty's GTK binding library is very well 
suited.

You can find the results from the pilot project in the GHC CVS repository at
 fptools/hslibs/object-io

The current state of affairs is due to severe lack of time a little 
unsatisfactory... To make this project manageable, it would be good to have 
some kind of automatic translator (nothing fancy, just a specialised 
translator from Clean Object I/O to Haskell Object I/O would do) that will 
derive the Haskell version from the Clean version that I do maintain. I 
haven't had time yet to make such a tool.

Regards,
Peter Achten

--
[1] Peter Achten and Simon Peyton Jones, Porting the Clean Object I/O 
Library to Haskell, in Mohnen, M. and Koopman, P. (eds) Proceedings of 
12th International Workshop Implementation of Functional Languages, 
IFL2000, Aachen, Germany, September 2000, Selected Papers, Springer, LNCS 
2011, pp. 194-213.

ftp://ftp.cs.kun.nl/pub/Clean/papers/2001/achp2001-HaskellObjectIO.ps.gz
ftp://ftp.cs.kun.nl/pub/Clean/papers/2001/achp2001-HaskellObjectIO.pdf


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



Re: The future of Haskell discussion

2001-09-14 Thread exa

-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1

On Friday 14 September 2001 12:52 pm, Marcin 'Qrczak' Kowalczyk wrote:
 I think it should be easy to add support for C++, except exceptions.

 There are two approaches: call C++ functions directly (it requires
 implementing name mangling by the Haskell compiler; there are several
 name mangling schemes and gcc changed its scheme in version 3.0)
 or write C wrappers (this is inconvenient but is doable now without
 compiler support).

 An annoyance is that templates can't be called directly but each
 instance must be imported separately.


I understand that you ought to deal with name mangling at some stage, but how 
would the interfaces ultimately look like? Say, for instance virtual 
functions, classes, sub classes, constructors, destructors?

If you can do non-template C++, then it wouldn't be difficult to call 
template code. Just do an explicit instantiation of the template code in an 
auto-generated .cxx file. What's the problem there?

 On Linux it works when main() of a mixed C/C++ program is written in C.
 AFAIK it doesn't work everywhere. Nevertheless an example I've now
 made worked.


It's about the linker used I guess. You should be able to do that.

 hsc2hs and ghc need to be extended to make it work smoothly. hsc2hs
 produces a file with extension .c and ghc compiles these files by
 passing -x c options to the C compiler, so even if a C++ compiler is
 substituted, it is compiled as C. There should be a switch in hsc2hs
 to let it produce C++ and ghc should recognize .cc extension, or
 in some other way ghc should be informed that the .c file is really
 C++. Option -pgmlg++ causes ghc to link using g++; option -lstdc++
 instead also works. And hsc2hs should be taught about extern C.

Writing another such translator would be necessary. After all, C++ is another 
language. It would be quite tricky to do that. It's halfway writing a C++ 
front-end, and would require an amount of deep magic. Even a standard 
conformant parser alone is quite difficult. Anybody give it a shot? :)

Thanks,

- -- 
Eray Ozkural (exa) [EMAIL PROTECTED]
Comp. Sci. Dept., Bilkent University, Ankara
www: http://www.cs.bilkent.edu.tr/~erayo
GPG public key fingerprint: 360C 852F 88B0 A745 F31B  EA0F 7C07 AE16 874D 539C
-BEGIN PGP SIGNATURE-
Version: GnuPG v1.0.6 (GNU/Linux)
Comment: For info see http://www.gnupg.org

iD8DBQE7ohx4fAeuFodNU5wRAlF9AKCnpE7xO3QzI8qeqih9coifE0Td4wCfT+gj
aOKIFCV6yu1XEB4oUHmGvI8=
=UR1s
-END PGP SIGNATURE-

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



Re: The future of Haskell discussion

2001-09-14 Thread Marcin 'Qrczak' Kowalczyk

Fri, 14 Sep 2001 18:04:24 +0300, Eray Ozkural [EMAIL PROTECTED] pisze:

 I understand that you ought to deal with name mangling at some stage,
 but how would the interfaces ultimately look like?

It depends how sophisticated tools we create. The easy step is to
wrap everything in functions. They would be C functions for the moment.
For example a plain method would be wrapped in a C function with 'this'
as one of arguments.

With C++ support in the Haskell compiler it can be more convenient
for overloaded functions and even non-virtual methods. Unfortunately
for calling a virtual method or getting a field out of a struct/class
it's not enough to supply what the programmer sees (function name
and types involved) to generate the code; the object layout matters.

Currently ghc doesn't deal with C/C++ object layout at all, and I
imagine it would be very hard for it to do this (how to interpret
a C++ header?). OTOH tools like hsc2hs and c-hs can support this;
they already can handle C struct fields.

I think calling a virtual method requires creating a function wrapper,
but tools should cope with this in future.

 If you can do non-template C++, then it wouldn't be difficult to
 call template code. Just do an explicit instantiation of the template
 code in an auto-generated .cxx file. What's the problem there?

Usually it should not be a problem, because arbitrary Haskell
objects can be represented only as something like StablePtr in C++,
so templates working on Haskell objects don't need many instantiations.

But a sophisticated cooperation between Haskell and C++ should
probably create custom C++ classes for wrapping different kinds of
Haskell objects, and then clients of a Haskell interface to a C++
library must instantiate templates themselves.

-- 
 __(  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: The future of Haskell discussion

2001-09-14 Thread Bill Halchin

Hello,
 Probably this question has been brought before. Besides the Preludes, why doesn't
Haskell have libraries like Java, Squeak (Smalltalk). I found this:
http://www.cit.gu.edu.au/~arock/hlibs/
Please take a look at .pdf files. Also I remember there was a Russian (actually
Georgian) guy who wrote a paper and Haskell as a proposal for a computer algebra
library. In the insuing discussion did his computer algebra come to nothing?

Regards, Bill HalchinGet your FREE download of MSN Explorer at http://explorer.msn.com

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


Re: The future of Haskell discussion

2001-09-14 Thread Jeffrey Palmer

On Fri, 2001-09-14 at 15:12, Mark Carroll wrote:
 On Fri, 14 Sep 2001, Bill Halchin wrote:
 
 Probably this question has been brought before. Besides the Preludes,
  why doesn't
  
  Haskell have libraries like Java, Squeak (Smalltalk). I found this:
 (snip)
 
 I'm puzzled - it does! - see http://www.haskell.org/libraries/ for some of
 them.
 

I think the question is more along the lines of Why doesn't Haskell
come bundled with complete, useful and _supported_ libraries?

For example, the Edison home page describes the library in this way: 

in its current state, the library is mostly a framework.  That is, I
provide signatures, but not yet very many implementations...  

This is not the type of thing that your standard software engineer wants
to hear.  Professional software developers need to be highly productive,
and are often unwilling to invest time learning libraries that aren't
part of the core language environment.  However you feel about the
design of the Java Collections API, at least it's a supported part of
the language.  Developers feel comfortable that any time spent learning
the how to use these APIs is worthwhile.

I felt this very recently when looking for a quality GUI framework for
Haskell.  There appear to be many(!) libraries available, and all seem
to be in various states of completion.  Personally, I would like to see
someone complete the port of the Clean library that was attempted, as
that library seems to have been pretty battle-tested, and there are lots
of good, real-world examples.

That, I suppose, is the key point.  Whatever libraries are chosen for
final inclusion in the Haskell environment, they should be treated as
integral to the language experience.  Extensive documentation and
examples should exist, perhaps of book length (I really liked Hudak's
text for this reason, and only wish that it had been written with the
standard Haskell GUI libs).  Finally, any libraries should be beaten
upon to such an extent that there is a solid guarantee that they are
safe for production use.

Thoughts?

- j


-- 
Jeffrey Palmer
Curious Networks, Inc.
http://www.curiousnetworks.com
e: [EMAIL PROTECTED]


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



Re: The future of Haskell discussion

2001-09-14 Thread S. Alexander Jacobson

If the GUI is based on the IO monad, then it doesn't seem like there is
a lot of advantage  to doing it in Haskell.  It seems like a better
idea to use a more natural language for IO and make RPC/interproc calls
to a haskell server to get stuff done.

In other words, what is the value of the GTK+ haskell interface?
Shouldn't more effort be put into getting Fruit production quality and/or
figuring out how to use arrows to manage textual and network IO?

-Alex-

___
S. Alexander Jacobson   Shop.Com
1-646-638-2300 voiceThe Easiest Way To Shop (sm)



On Fri, 14 Sep 2001, Manuel M. T. Chakravarty wrote:

 S. Alexander Jacobson [EMAIL PROTECTED] wrote,

  Out of curiosity, how does GTK+ compare with Fruit?

 GTK+ has a C API heavily based on call backs and mutable
 state.  Thus, the Haskell transcription of that API heavily
 relies on the use of the IO monad - as does H98 textual IO.

  It seems like it would make sense for the standard Haskell GUI also to be
  functional.

 A functional GUI would be nice, but standard Haskell text
 and file I/O is not functional either.  Functional GUIs like
 Fruit are from a research perspective very interesting, but
 their design is rather far from being a solved problem,
 which makes them a not very likely candidate for a standard
 that people seem to like to have sooner rather than later.

 Cheers,
 Manuel


 ___
 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

2001-09-14 Thread Alastair David Reid


 If the GUI is based on the IO monad, then it doesn't seem like there is
 a lot of advantage  to doing it in Haskell.  It seems like a better
 idea to use a more natural language for IO and make RPC/interproc calls
 to a haskell server to get stuff done.

In other words, if you use the IO monad, you're going to have the same
programming experience (only more verbose) as a C/C++/Java programmer?

I don't think that's true.

My graphics library (http://haskell.org/graphics/) uses the IO monad
for manipulating windows and the Draw monad for doing graphics but
both feel quite different from similar code I've written in C (and, I
believe, from C++ or Java code).

In the case of manipulating windows, the different feel comes from
using concurrency to hide the event loop and from using layers of
abstraction to hide the full power (and horror) of the X and Win32
programming models.

In the case of the Draw monad (which is identical to the
IO monad except that it carries a device context around as an
implicit parameter), the different feel comes from aggressive
use of continuations (actually, they're not quite continuations
but I don't have a better word for them).  For example, you might
normally write code like this:

  do
old_color - selectColor blue
old_font  - selectFont  helvetica
write_text Hello World
selectFont  old_font
selectColor old_color

(Reselecting the old color and font at the end is recommended Win32
programming style.)

In the HGL, you instead write:

  setPicture window (withColor blue (withFont helvetica (text Hello World)))

or, equivalently but allegedly easier to read,

  setPicture window$
withColor blue $
withFont helvetica $
text Hello World

where withColor and withFont are defined like this:

  withColor :: Color - Draw a - Draw a
  withColor c m = do{ old - selectColor c; a - m; selectColor old; return a }

  withFont  :: Font  - Draw a - Draw a
  withFont f m = do{ old - selectFont f; a - m; selectFont old; return a }

and setPicture exploits the fact that an object of type Draw a is a
first class object which can be stored in the window state and
executed when appropriate (e.g., when the window is uniconified).


What I'm saying is that Haskell's standard abstraction facilities mean
that even in the IO monad your programming experience can
significantly better than that of a C programmer.  (Of course your
experience can also be worse if you don't or can't bring Haskell's
strengths to bear on your problem.)


-- 
Alastair Reid[EMAIL PROTECTED]http://www.cs.utah.edu/~reid/

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



Re: The future of Haskell discussion

2001-09-14 Thread Mark Carroll

On 14 Sep 2001, Jeffrey Palmer wrote:
(snip) [ good stuff ]
 Thoughts?

A shortage of volunteers? I get the impression that there's a reasonable
consensus on what needs to be done; it's just that too few of us have the
time and expertise to execute it.

-- Mark


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



Re: The future of Haskell discussion

2001-09-13 Thread kahl


Marcin 'Qrczak' Kowalczyk [EMAIL PROTECTED] asks:
 
 12 Sep 2001 12:37:25 -, [EMAIL PROTECTED] 
[EMAIL PROTECTED] pisze:
 
  * Currently HOPS implements only one evaluation strategy,
namely leftmost outermost graph rewriting with sharing preservation
(without automatic sharing maximisation).
With the standard rules in place, this corresponds
to the original definition of lazy evaluation
(also known as the ``D-rule''), which is different
from the lazy pattern matching evaluation
of sequential Haskell implementations.
 
 What is the difference?

If you have

f x [] = 0
f x (y:ys) = 1 + f x ys

bot = bot

and consider the redex

f bot (enumFromTo 1 2)

then leftmost outermost rewriting (sharing is irrelevant here) diverges:

f bot (enumFromTo 1 2) - 
f bot (enumFromTo 1 2) - ...

while the ``functional strategy'' finds out that the second argument
needs to be evaluated first, and terminates:

f bot (enumFromTo 1 2) -
f bot (1 : enumFromTo 2 2) -
1 + f x (enumFromTo 2 2) -
1 + f x (2 : enumFromTo 3 2) -
1 + (1 + f x (enumFromTo 3 2)) -
1 + (1 + f x []) -
1 + (1 + 0) -
1 + 1 -
2


For a definition of the functional rewriting strategy
see for example p. 139f in:

@Book{Plasmeijer-vanEekelen-1993,
  author =   {Rinus Plasmeijer and van Eekelen, Marko},
  title ={Functional Programming and Parallel Graph Rewriting},
  publisher ={Addison-Wesley},
  year = 1993,
  series =   {International Computer Science Series},
  ISBN = {0-201-41663-8}
}

The fact that Haskell uses the functional strategy
should also follow from the translation for function bindings
given in the Haskell report, section 4.4.3

http://research.microsoft.com/~simonpj/haskell98-revised/haskell98-report-html/decls.html#sect4.4.3

in conjunction with the pattern matching semantics, section 3.17.

http://research.microsoft.com/~simonpj/haskell98-revised/haskell98-report-html/exps.html#pattern-matching


However, I already have troubles with
the first sentence of 3.17.2 ``Informal Semantics of Pattern Matching'':

http://research.microsoft.com/~simonpj/haskell98-revised/haskell98-report-html/exps.html#sect3.17.2

which says: ``Patterns are matched against values.'':

Variables are patterns, and in the above example,
the variable x is matched against the non-value bot ---
if my understanding of values is correct.
(Also, the direction of ``matching against'' in this
sentence is contrary to that used in most of the explanations that follow
after it.)

For the examples section of 3.17.2,
perhaps one might add an example under item 1. that illustrates this effect:

| If (x,'b') is matched against (_|_,'b'),
| the match succeeds and binds x to _|_.



Wolfram




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



Re: The future of Haskell discussion

2001-09-13 Thread Manuel M. T. Chakravarty

Olaf Chitil [EMAIL PROTECTED] wrote,

 Here a short summary by Malcolm and me of the final discussion at the
 Haskell workshop:

I also took a couple of notes which I like to add.

 John Launchbury and many further people made a plea that the single
 biggest hindrance to the further spread of Haskell is the lack of a
 standard
 cross-platform GUI. Alas, no answer to the problem was found. There is
 no agreement which (existing) library could be the basis of a standard
 one and nobody wanted to commit himself to developing and supporting
 such a library. Well, Manuel Chakravarty promised to continue developing
 the GTK+ binding and would be happy about people helping him. (The GUI
 library presented at the workshop is not intended to solve the standard
 GUI problem.)

In fact, the recent release of binary packages for Gtk+HS
and an example applications that demonstrates how to use
the GTK+ API in Haskell have been a reaction to the
discussions at HW  ICFP.

Let me reiterate: Gtk+HS as it is today is sufficient for
applications requiring a GUI of medium complexity.  As far
as I see, despite not covering all of GTK+ yet, Gtk+HS
already has a wider variety of widgets and functionality
than Tcl/Tk provides in its whole API.  So, at least on
Unix, the statement that there is no GUI for Haskell is just
not valid anymore.  For Win32, somebody would have to set up
the binding for use with the Win32 port of GTK+.  I am happy
to include any patches coming out of this into the main
distribution.

You can see how programs coded against the GTK+ API in
Haskell look like at the following example:

  http://www.cse.unsw.edu.au/~chak/haskell/gtk/BoolEd.html

(As for Unix/Win32 portability of GUI code, that's not great
for C or C++ either.)

 Rather than starting work on a successor to Haskell, people
 generally want to see `blessed addendums' to the Report,
 for common agreed extensions, e.g. FFI, exceptions,
 concurrency, MPTC, fundeps, etc.  The FFI addendum is almost ready,
 but any others need volunteers, not to mention agreement between
 designers and implementations.  The idea is that a solid
 reference definition/documentation of each extension should
 exist independent of any particular compiler (but there is a lack
 of volunteers).
 
 It was noted that the future job of designing Haskell-2 will be
 made much easier by many small steps rather than one large effort.

Generally, as last year, there seemed to be not much
interest to look into Haskell 2.  Meanwhile, addenda to H98
seem to be a feasible alternative.  In fact, one aim with
the FFI Addendum was to create a precedent that can be
repeated for other extensions.

The nature of an addendum brings with it that the extension
should be rather non-invasive.  For example, in the case of
the FFI, one new keyword (`foreign') is added, taking it from
the pool of available variable identifiers.  The rest of the
functionality should not invalidate any existing H98
programs.  As a consequence, the kind of extensions that can
be realised in this way are limited.  For example,
extensions of the type system are much more likely to have a
severe effect on existing H98 programs.  So, they will be
less easy to add in this form.

It was also pointed out that we should go for an addendum
only where

- the design is clear and tested (example implementations
  exist and have been used in applications) and

- where there is considerable demand.

The first point is surely self-explanatory.  As for the
second, defining an addendum is a lot of work, which can be
used better otherwise unless the extension is really
important. 

Possible further addenda (in addition to the FFI), which
have been mentioned, are the following:

- The core library (in fact, there is already exists a task
  force to look into this extension)
- Concurrency support (there just are applications that are
  virtually impossible to implement well without
  concurrency)
- Exceptions (again a really elementary feature of modern
  languages) 
- Graphics library (obviously there is a lot of demand, but
  it is also a rather involved task)

In my opinion, all the above functionality falls into the
catergory embarrassing not to have.  The lack therefore, in
fact, promotes the image of Haskell being an academic toy
language.  The only exception is to a degree the graphics
library (again my opinion, which obviouly is not shared by
everybody, most notably John Launchbury).  My reason is
that, while access to GUI toolkits is a must, few languages
standardise them.

Type extensions (multi-parameter type classes, existential
types, rank-2 polymorphism, etc.) have been mentioned, but
it seemed that there isn't really a consus as to how they
should exactly be implemented and whether they are really so
urgently needed.  Moreover, they tend to be more invasive.
Personally, I would believe that multi-parameter type
classes may maybe be the most likely candidate for an
addendum. 

There was the feeling that there is not frequent 

Re: The future of Haskell discussion

2001-09-13 Thread S. Alexander Jacobson

Rather than talking about general features of the language that might
improve adoption in general, it is more useful to talk about specific
features of the language that make it killer in a particular application
domain.

In his classic book, Crossing the Chasm : Marketing and Selling High-Tech
Products to Mainstream Customers, Geoffrey Moore argues that the way to
gain mainstream adoption of a new technology is to target specific
segments of the customer population and to deliver whole product to them
(because integration challenges are daunting).

In http://www.paulgraham.com/lib/paulgraham/bbnexcerpts.txt, Paul Graham
argues that:
   One of the reasons to use Lisp in writing Web-based applications
   is that you *can* use Lisp.  When you're writing software that is
   only going to run on your own servers, you can use whatever language
   you want.

And further that:
   Until recently, writing application programs meant writing software to
   run on desktop computers.  In desktop software there was a strong bias
   toward writing the application in the same language as the operating
   system.

I would add that web based applications can use web interfaces and that
HTML is a good interface to many applications.  (and that Paul Graham's
comments about Lisp are also true of Haskell)

As such, I would like to see a focus on making Haskell great for web
application and web service development.  Some of the the pieces required
are application level, some are libraries, and some are language features.
Here is my quick take:

Application Framework
* a simple build/install process on both unix and win32
* a way to run/link haskell applications to a web server (apache)
* a decent libary organization and CPAN-like library sharing system
* a system for publishing apps to live servers

Libraries
* an OS file/directory access library
* a database connection library (even just ODBC would be fine!)
* a database connection pool library
* a mail handling library
* an XML parser library
* an XML-RPC/SOAP library

Language Features
* concurrency (to make requests to multiple servers simultaneously)
* FFI (to access libraries in other languages)
* exceptions (may not matter depends on the webserver/haskell interface!)

Documentation
* an O'Reilly class book on learning and developing web apps in Haskell
* sample applications that demonstrate useful web service functions
* a process for managing Haskell web app development

As a general matter, the addendum process strikes me as confusing and
dangerous.  I don't want to have a conversation like: I am using
Haskell'98 with Addendum A, C, and E.  I'd rather say, I am using Haskell
2001 and know that it is useful for developing web apps.

I know this is a lot of work, but it was what you get from Python, Perl,
and Java.  If Haskell wants to compete in this arena, it needs to provide
this level of service.  Also, I think a lot of these exist in pieces, so
the real work is in compiling it all into a good usable package.  I am not
volunteering to do it, but I would be happy to help beta if someone else
does.

-Alex-

PS There may be other better/easier initial application domains for
Haskell, but this is what I know.


___
S. Alexander Jacobson   Shop.Com
1-646-638-2300 voiceThe Easiest Way To Shop (sm)



On Fri, 14 Sep 2001, Manuel M. T. Chakravarty wrote:

 Olaf Chitil [EMAIL PROTECTED] wrote,

  Here a short summary by Malcolm and me of the final discussion at the
  Haskell workshop:

 I also took a couple of notes which I like to add.

  John Launchbury and many further people made a plea that the single
  biggest hindrance to the further spread of Haskell is the lack of a
  standard
  cross-platform GUI. Alas, no answer to the problem was found. There is
  no agreement which (existing) library could be the basis of a standard
  one and nobody wanted to commit himself to developing and supporting
  such a library. Well, Manuel Chakravarty promised to continue developing
  the GTK+ binding and would be happy about people helping him. (The GUI
  library presented at the workshop is not intended to solve the standard
  GUI problem.)

 In fact, the recent release of binary packages for Gtk+HS
 and an example applications that demonstrates how to use
 the GTK+ API in Haskell have been a reaction to the
 discussions at HW  ICFP.

 Let me reiterate: Gtk+HS as it is today is sufficient for
 applications requiring a GUI of medium complexity.  As far
 as I see, despite not covering all of GTK+ yet, Gtk+HS
 already has a wider variety of widgets and functionality
 than Tcl/Tk provides in its whole API.  So, at least on
 Unix, the statement that there is no GUI for Haskell is just
 not valid anymore.  For Win32, somebody would have to set up
 the binding for use with the Win32 port of GTK+.  I am happy
 to include any patches coming out of this into the main
 distribution.

 You can see 

Re: The future of Haskell discussion

2001-09-13 Thread Mark Carroll

On Thu, 13 Sep 2001, S. Alexander Jacobson wrote:
(snip)
 As such, I would like to see a focus on making Haskell great for web
 application and web service development.  Some of the the pieces required
 are application level, some are libraries, and some are language features.
 Here is my quick take:
(snip)
 I know this is a lot of work, but it was what you get from Python, Perl,
 and Java.  If Haskell wants to compete in this arena, it needs to provide
 this level of service.  Also, I think a lot of these exist in pieces, so
 the real work is in compiling it all into a good usable package.  I am not
(snip)

For what little it's worth, I'm encouraged just to see people talking like
this lately: such things would make a lot of difference in making me much
more comfortable about using Haskell for non-trivial commercial
projects.

-- Mark


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



Re: The future of Haskell discussion

2001-09-13 Thread C.Reinke


 There was the feeling that there is not frequent enough
 feedback from the Task Forces (eg, FFI Task Force, Library
 Task Force) to the Haskell community as a whole.  Clause
 Reinke kindly volunteered to collect status reports of Task
 Forces on a 6-monthly basis and post them to the Haskell
 mailing list.  
 
 Claus, maybe you should give the Task Forces an idea of when
 you expect the first status report.

Just a quick update: when I was volunteered for organising more
frequent feedback from the task forces to the Haskell community as a
whole, I thought of just collecting individual summaries from the
existing lists. However, my current opinion on the matter is that this
alone would actually be a bad idea, as there are too many lists, no
lists for some important topics, some topics spread over several lists,
and generally not enough useful structure for the wide range of Haskell
sub-communities.

So what has been holding up the call for status reports from here
(apart from the usual real work:-) is my attempt to (a) gather as
many of the various Haskell interest groups as I can and (b) find some
way to organise them, so that I get an idea of who is out there and how
the pieces might fit together. I won't even try to get everything right
in the first go, so I hope to send round a first draft of a structure
(based on existing info at haskell.org and elsewhere) in the next
days.  The main point I'm still undecided on is at what level to ask
for status reports.

In my current version of the hierarchy, there are three levels, with
4-5 broad areas at the top (such as libraries, implementations, etc.),
and many of the existing mailing lists or projects, such as Gtk+HS, at
the most detailed level. If our community was more organised, I would
really like to see reports at the middle (e.g., what's up in terms of
GUIs?-) or top level, but as it stands, I will probably need to look
for anything I can get at the mailing-list level and then try to edit
all those fragments into a more useful overview.

For the timescale, I still think that 6-monthly reports are a sensible
compromise, and the Haskell workshops are a good reference point. I'll
ask for the first status reports as soon as I've got an idea of how
everything might fit together, probably early next week. The second
round will then take place in between Haskell workshops, and so on.

It would be nice if we could cover not only the explicit task forces,
but all Haskell (sub-)communities (such as the folks interested in
generic programming, or in concurrent/parallel/distributed programming,
functional reactive programming, etc.). That'll mean that the
individual status reports themselves will have to be brief (plus
pointers to more detailed documents, and instructions about how to join
the communities or find archives), which should also make it easier to
find people who write them;-).

More later,
Claus


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



Re: The future of Haskell discussion

2001-09-13 Thread Frank Atanassow

Just a quick remark:

S. Alexander Jacobson wrote (on 13-09-01 12:40 -0400):
 As a general matter, the addendum process strikes me as confusing and
 dangerous.  I don't want to have a conversation like: I am using
 Haskell'98 with Addendum A, C, and E.  I'd rather say, I am using Haskell
 2001 and know that it is useful for developing web apps.

Eventually, you will be saying that, but about Haskell-2.

In the interim, having extensions described in addendums is probably better
than the situation we have now, in which you are forced to say that I am
using Haskell with extension X (but with whose semantics?) or I am using GHC
Haskell (but Hugs also supports my extension). At least if an extension is
described in a Haskell Report Addendum one knows where to look for its
semantics, that its semantics are standardized, and that it is reasonably
accepted by the community and not some Bizarro (I love that word :) extension
which will only ever be implemented in some obscure researcher's pet compiler
project.

-- 
Frank Atanassow, Information  Computing Sciences, Utrecht University
Padualaan 14, PO Box 80.089, 3508 TB Utrecht, Netherlands
Tel +31 (030) 253-3261 Fax +31 (030) 251-379

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



Re: The future of Haskell discussion

2001-09-13 Thread Wolfgang Jeltsch

On Thursday, 13. September 2001 17:50, Manuel M. T. Chakravarty wrote:
 [...]
 Let me reiterate: Gtk+HS as it is today is sufficient for
 applications requiring a GUI of medium complexity.  As far
 as I see, despite not covering all of GTK+ yet, Gtk+HS
 already has a wider variety of widgets and functionality
 than Tcl/Tk provides in its whole API.  So, at least on
 Unix, the statement that there is no GUI for Haskell is just
 not valid anymore.  For Win32, somebody would have to set up
 the binding for use with the Win32 port of GTK+.  I am happy
 to include any patches coming out of this into the main
 distribution.

In my opinion GTK+ is not that nice to develop Win32 applications because it 
provides its own look-and-feel which conflicts with the one of Windows. On 
UNIX-like systems where each desktop environment has its own look-and-feel it 
does not conflict under GNOME because GNOME is based on it. That's why I 
think GTK+ should be used mainly to develop applications which are intended 
to run under GNOME and preferably not to do cross-plattform GUI programming. 
I think the best solution for the latter thing is to use a library which has 
multiple implementations based on different native libraries like Win32, 
GTK+, Qt. wxWindows (http://www.wxwindows.org/) is an example for this kind 
of library.

 [...]
 Type extensions (multi-parameter type classes, existential
 types, rank-2 polymorphism, etc.) have been mentioned, but
 it seemed that there isn't really a consus as to how they
 should exactly be implemented and whether they are really so
 urgently needed.

I need at least multi-parameter type classes urgently. I am currently working 
on a software package allowing website implementation in Haskell which relies 
on them.

 [...]

Wolfgang

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



RE: The future of Haskell discussion

2001-09-13 Thread brk



 In my opinion GTK+ is not that nice to develop Win32 applications because
 it 
 provides its own look-and-feel which conflicts with the one of Windows. On
 
 UNIX-like systems where each desktop environment has its own look-and-feel
 it 
 does not conflict under GNOME because GNOME is based on it. That's why I 
 think GTK+ should be used mainly to develop applications which are
 intended 
 to run under GNOME and preferably not to do cross-plattform GUI
 programming. 
 I think the best solution for the latter thing is to use a library which
 has 
 multiple implementations based on different native libraries like Win32,
 
 GTK+, Qt. wxWindows (http://www.wxwindows.org/) is an example for this
 kind 
 of library.
 
[Bryn Keller]  
Yes, exactly. Additionally, I have had trouble with bugginess in GTK
on Win32 (not the Haskell bindings, but GTK itself), and things which want
to compile with GTK usually insist on using an executable called gtk-info
(IIRC) or something similar -- but on windows, only the DLLs are available
(last time I checked).

My personal vote would be for wxWindows - it's good stuff, and it's
free even for commercial use. Qt's main advantage IMHO is in
internationalization.

The thing I'd most like to see, however, is not a standard C++
toolkit, but a standard Haskell GUI API which could then be implemented on
top of other things (wxWindows, GTK, OpenGL, XUL, etc.). Frantk is
implemented something like this I believe, and Fruit also has an interesting
(if young) model.


Bryn

  

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



Re: The future of Haskell discussion

2001-09-13 Thread Manuel M. T. Chakravarty

Wolfgang Jeltsch [EMAIL PROTECTED] wrote,

 That's why I 
 think GTK+ should be used mainly to develop applications which are intended 
 to run under GNOME and preferably not to do cross-plattform GUI programming. 
 I think the best solution for the latter thing is to use a library which has 
 multiple implementations based on different native libraries like Win32, 
 GTK+, Qt. wxWindows (http://www.wxwindows.org/) is an example for this kind 
 of library.

wxWindows is quite C++ centric and AFAIK nobody has made a
serious effort at a C++ FFI yet.  One of the big advantages
of GTK+ is that it was written with bindings for other
languages in mind.  Therefore, it is probably the toolkit
with the most language bindings.

One alternative would be to standardise on a kind of subset
of the GTK+ API and then somebody with a lot of spare time
could implement that on top of the Win32 API natively - in
the meantime, the original GTK+ libraries would at least
provide some form of implementation under Win32.  (You
should bear in mind that anything that doesn't build on
existing infrastructure involves a lot of coding and I
haven't seen many volunteers stepping forward yet.)

Manuel

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



Re: The future of Haskell discussion

2001-09-13 Thread Mark Carroll

On Fri, 14 Sep 2001, Manuel M. T. Chakravarty wrote:
(snip)
 wxWindows is quite C++ centric and AFAIK nobody has made a
 serious effort at a C++ FFI yet.  One of the big advantages
(snip)

Of course, wxPython also exists - I assume that the emphasis on object
orientation is the problem?

-- Mark


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



Re: The future of Haskell discussion

2001-09-13 Thread S. Alexander Jacobson

Out of curiosity, how does GTK+ compare with Fruit?
It seems like it would make sense for the standard Haskell GUI also to be
functional.

-Alex-

PS I don't do GUI stuff so I don't really know much.  I did read the Fruit
paper and it looked interesting.



On Fri, 14 Sep 2001, Manuel M. T. Chakravarty wrote:

 Wolfgang Jeltsch [EMAIL PROTECTED] wrote,

  That's why I
  think GTK+ should be used mainly to develop applications which are intended
  to run under GNOME and preferably not to do cross-plattform GUI programming.
  I think the best solution for the latter thing is to use a library which has
  multiple implementations based on different native libraries like Win32,
  GTK+, Qt. wxWindows (http://www.wxwindows.org/) is an example for this kind
  of library.

 wxWindows is quite C++ centric and AFAIK nobody has made a
 serious effort at a C++ FFI yet.  One of the big advantages
 of GTK+ is that it was written with bindings for other
 languages in mind.  Therefore, it is probably the toolkit
 with the most language bindings.

 One alternative would be to standardise on a kind of subset
 of the GTK+ API and then somebody with a lot of spare time
 could implement that on top of the Win32 API natively - in
 the meantime, the original GTK+ libraries would at least
 provide some form of implementation under Win32.  (You
 should bear in mind that anything that doesn't build on
 existing infrastructure involves a lot of coding and I
 haven't seen many volunteers stepping forward yet.)

 Manuel

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


___
S. Alexander Jacobson   Shop.Com
1-646-638-2300 voiceThe Easiest Way To Shop (sm)


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



Re: The future of Haskell discussion

2001-09-12 Thread Olaf Chitil


Here a short summary by Malcolm and me of the final discussion at the
Haskell workshop:

First Simon Peyton Jones stated that the Haskell'98 Report continues to
be revised in small ways for correctness and readability.  He will
continue this
until a whole month passes with no further changes, then issue a
finalised new version (so send bug reports now).

John Launchbury and many further people made a plea that the single
biggest hindrance to the further spread of Haskell is the lack of a
standard
cross-platform GUI. Alas, no answer to the problem was found. There is
no agreement which (existing) library could be the basis of a standard
one and nobody wanted to commit himself to developing and supporting
such a library. Well, Manuel Chakravarty promised to continue developing
the GTK+ binding and would be happy about people helping him. (The GUI
library presented at the workshop is not intended to solve the standard
GUI problem.)

Rather than starting work on a successor to Haskell, people
generally want to see `blessed addendums' to the Report,
for common agreed extensions, e.g. FFI, exceptions,
concurrency, MPTC, fundeps, etc.  The FFI addendum is almost ready,
but any others need volunteers, not to mention agreement between
designers and implementations.  The idea is that a solid
reference definition/documentation of each extension should
exist independent of any particular compiler (but there is a lack
of volunteers).

It was noted that the future job of designing Haskell-2 will be
made much easier by many small steps rather than one large effort.



My personal comment about application letters: I think your idea of a
poster session with abstracts in the proceedings is very good. In fact,
anybody already had the possiblity to give a 10 minute talk. But there
was no special invitation to talk about applications and an abstract
would certainly be useful for people not attending or future reference.


Here a list of the 10 minute talks given at the workshop (Ralf, maybe
you can put them on the workshop web page?):

Simon Marlow: Haskell Libraries, The Next Generation
Presentation of the hierarchical structure. Need more libraries and
maintainers for them. Would like to have HaskellDoc and some standard
testing method.

Mark Shields: Lightweight Modules for Haskell
Shortly stated that he is working on a new module system and would like
every interested person to join.

Wolfram Kahl: Animating Haskell by Term Graph Rewriting
HOPS is a system for term graph rewriting that can also show the
rewriting steps in a graphical animation. Similar to GHood but all
intermediate redexes are shown. Translation of Haskell programs into
HOPS by hand. Useful especially for understanding space leaks. 

Martin Sulzmann: TIE: A CHR-based Type Inference Engine
He reformulates context simplification of Haskell classes in the
constraint handling rule formalism. This gives a flexible framework for
all kinds of extensions and variants of class systems. 

Manuel Chakravarty: A standard Foreign Function Interface for Haskell98
Basically finished (general part and C, not for Java). Solicits last
comments from the general community.


-- 
OLAF CHITIL, 
 Dept. of Computer Science, University of York, York YO10 5DD, UK. 
 URL: http://www.cs.york.ac.uk/~olaf/
 Tel: +44 1904 434756; Fax: +44 1904 432767

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



Re: The future of Haskell discussion

2001-09-12 Thread kahl

Olaf Chitil [EMAIL PROTECTED] summarised the 10 minute talks
of this years Haskell workshop, including my presentation:
 
 Wolfram Kahl: Animating Haskell by Term Graph Rewriting
 HOPS is a system for term graph rewriting that can also show the
 rewriting steps in a graphical animation. [...]

For clarification, a few core points:

* I have a GHC extension, called MHA (for ``Munich Haskell Animator'')
  that automatically converts programs written in a subset of Haskell
  into HOPS modules. This is not yet publicly available,
  but this may change in the future. Contact me if interested.

* Animation in HOPS can show every intermediate step,
  but it is also possible to show only a selection,
  currently by the module where the applied rules reside.

  On a 1.2GHz Athlon, I currently get up to over 1000 raw rule applications
  per second, and around 10 graph drawings per second, so
  striking some reasonable balance can be quite helpful.

  The current version of HOPS awaits mostly a thorough documentation
  update for release.

  The HOPS home page is: http://ist.unibw-muenchen.de/kahl/HOPS/

* Currently HOPS implements only one evaluation strategy,
  namely leftmost outermost graph rewriting with sharing preservation
  (without automatic sharing maximisation).
  With the standard rules in place, this corresponds
  to the original definition of lazy evaluation
  (also known as the ``D-rule''), which is different
  from the lazy pattern matching evaluation
  of sequential Haskell implementations.

  Naive translations can therefore yield inappropriate results,
  and for some Haskell programs this is still the case
  in the current version.
  Therefore, you have to understand the translation
  in order to be sure that what you see corresponds to
  what happens in the Haskell implementation.

  I hope to release MHA only after I have addressed this issue better
  than in the current version.

* For a variety of reasons, I would tend to say that the HOPS/MHA approach
  is really not very similar to GHood. Some of them may already
  be apparent from the above, others would go into more detail
  then I intend to do in this message.


Best regards,

Wolfram







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



Re: The future of Haskell discussion

2001-09-12 Thread Mark Carroll

It seems like a common thread is a shortage of willing programming effort
so that things may be maintained and improved. Would it be worth thinking
about how to promote Haskell in communities where people might be willing
and able to contribute to the work?

(Much thanks to the people who are already part of it.)

-- Mark


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



Re: The future of Haskell discussion

2001-09-12 Thread Marcin 'Qrczak' Kowalczyk

Wed, 12 Sep 2001 11:00:38 +0100, Olaf Chitil [EMAIL PROTECTED] pisze:

 Mark Shields: Lightweight Modules for Haskell
 Shortly stated that he is working on a new module system and would like
 every interested person to join.

I'm interested. How to join?

-- 
 __(  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: The future of Haskell discussion

2001-09-12 Thread Marcin 'Qrczak' Kowalczyk

12 Sep 2001 12:37:25 -, [EMAIL PROTECTED] 
[EMAIL PROTECTED] pisze:

 * Currently HOPS implements only one evaluation strategy,
   namely leftmost outermost graph rewriting with sharing preservation
   (without automatic sharing maximisation).
   With the standard rules in place, this corresponds
   to the original definition of lazy evaluation
   (also known as the ``D-rule''), which is different
   from the lazy pattern matching evaluation
   of sequential Haskell implementations.

What is the difference?

-- 
 __(  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