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: 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: 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: 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