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

Reply via email to