Re: Export lists in modules

2006-02-20 Thread Cale Gibbard
That seems sensible to me.

 - Cale

On 20/02/06, Jared Updike <[EMAIL PROTECTED]> wrote:
> > I am not sure if this has been mentioned before, but something I
> > would really find useful is the ability to tell Haskell to export
> > everything in a function except for some named functions.
>
> No one has responded so I thought I would make a suggestion about what
> the syntax might look like to do this. Currently the syntax to set
> what gets exports is:
> > module Module ( list, of, things, to, export ) where 
> and to hide things on import is
> > import Module hiding ( list, of, things, not, to, import )
>
> How about combining the two (since 'hiding' is already a reserved word):
>
> > module Module hiding ( list, of, things, not, to, export ) where 
>
> Everything gets exported except what you explicitly hide. Is this
> general enough? Are there reasons why this might not work? And does
> this solve your problem? Does anyone like this idea (aethestically and
> pragmatically)?
>
>   Jared.
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: the MPTC Dilemma (please solve)

2006-02-20 Thread Martin Sulzmann
Ross Paterson writes:
 > On Sat, Feb 18, 2006 at 12:26:36AM +, Ross Paterson wrote:
 > > Martin Sulzmann <[EMAIL PROTECTED]> writes:
 > > > Result2:
 > > > Assuming we can guarantee termination, then type inference
 > > > is complete if we can satisfy
 > > >- the Bound Variable Condition,
 > > >- the Weak Coverage Condition, 
 > > >- the Consistency Condition, and
 > > >- and FDs are full.
 > > > Effectively, the above says that type inference is sound,
 > > > complete but semi-decidable. That is, we're complete
 > > > if each each inference goal terminates.
 > > 
 > > I think that this is a little stronger than Theorem 2 from the paper,
 > > which assumes that the CHR derived from the instances is terminating.
 > > If termination is obtained via a depth limit (as in hugs -98 and ghc
 > > -fallow-undecidable-instances), it is conceivable that for a particular
 > > goal, one strategy might run into the limit and fail, while a different
 > > strategy might reach success in fewer steps.
 > 

Yes, the above is stronger than Theorem 2.

 > Rereading, I see you mentioned dynamic termination checks, but not
 > depth limits.  Can you say a bit more about termination?  It seems to
 > be crucial for your proofs of confluence.
 > 

A depth limit is not enough. For confluence we need that *all*
derivations for a particular goal terminate. Once we have
confluence we get completeness of the inference checks.

I think you're asking: If one derivation for a particular goal
terminates will all other derivations for that goal terminate as well?
(BTW, such a result can be proven for range restriction).
It might hold (assuming the usual restrictions, instances terminate,
weak coverage holds etc) by I'm not sure
(means, I couldn't come up with a counter-example but a formal proof
is still missing).

Martin
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: Pragmas for FFI imports

2006-02-20 Thread John Meacham
On Fri, Feb 17, 2006 at 01:45:27AM +0200, Einar Karttunen wrote:
> I would like to propose two pragmas to be included in Haskell'
> for use with FFI. One for specifying the include file defining
> the foreign import (INCLUDE in ghc) and an another for defining
> a library that the foreign import depends on, called FFI_LIB
> (not implemented at the moment). These changes would not break
> any existing code.

Just to expand on this, Einar is working on adding this support to jhc
right now in his work on the library system in jhc. the semantic we
decided on was that an

{-# INCLUDE "foo.h" #-}

in any module will have the equivalent effect of adding an include to
each foreign ccall in the current module like so:

foreign import ccall "foo.h foo" foo :: Int -> Int

I say equivalent effect because I know ghc treats includes somewhat
differently depending on where they are specified but the eventual
user visible effect is the same (I think, if I understand things)

the same will be true of the FFI_LIB flag,
{-# FFI_LIB libm #-}

foreign import ccall "-lm foo.h foo" foo :: Int -> Int
 (note: jhc non-standard syntax extension here)


John




-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: Export lists in modules

2006-02-20 Thread John Meacham
on this note, I thought it would be nice to do a 'mostly unqualified'
import.

import Foo qualified(foo,bar)

which will have the effect of 

import Foo hiding(foo,bar)
import qualified Foo(foo,bar)

since usually you can import a whole module unqualified except for a few
troublemakers.

John

-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: Export lists in modules

2006-02-20 Thread Christopher Brown

Jared,



How about combining the two (since 'hiding' is already a reserved  
word):



module Module hiding ( list, of, things, not, to, export ) where 


Everything gets exported except what you explicitly hide. Is this
general enough? Are there reasons why this might not work? And does
this solve your problem? Does anyone like this idea (aethestically and
pragmatically)?


This seems to make perfect sense to me, by having this syntax we can  
cater for three different exports:


export explicit functions only;
export everything in the module and
export everything except explicitly named functions.

Thanks.

Chris.




  Jared.


Christopher Brown
Ph.D. Student University of Kent. UK.
http://www.cs.kent.ac.uk/people/rpg/cmb21/index.html



___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: proposal: standardize interface to Haskell' implementations

2006-02-20 Thread John Meacham
On Mon, Feb 20, 2006 at 03:21:27PM -, Simon Peyton-Jones wrote:
> I, for one, would love it if you and others felt able to contribute to
> the Haskell-as-a-library interface (i.e. what it should look like to the
> client).  Whether we'd be anywhere near done for Haskell' I'm less
> certain.  

I personally wouldn't want to see such a thing in haskell'. It feels
like something that should be a portable library, not a part of the
language spec. There would be no reason to have multiple implementations
to standardize across, if someone wants to do something new and
interesting, those new and interesting things would be reflected in the
interface breaking the point of standardization anyway. We should be
thinking not what libraries we want to use, but rather what absolutely
needs to be in the language spec to allow the libraries we want to use
to be portable. I was always planning on spinning off the jhc front end
as a library, but it most likely would not be compatable with
ghc-as-a-library by design as it would have different goals and want to
explore different things. someone should be able to install both and use
them side by side. Artificial standardization would only hurt such a
project.

John

-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: Export lists in modules

2006-02-20 Thread Jared Updike
> I am not sure if this has been mentioned before, but something I
> would really find useful is the ability to tell Haskell to export
> everything in a function except for some named functions.

No one has responded so I thought I would make a suggestion about what
the syntax might look like to do this. Currently the syntax to set
what gets exports is:
> module Module ( list, of, things, to, export ) where 
and to hide things on import is
> import Module hiding ( list, of, things, not, to, import )

How about combining the two (since 'hiding' is already a reserved word):

> module Module hiding ( list, of, things, not, to, export ) where 

Everything gets exported except what you explicitly hide. Is this
general enough? Are there reasons why this might not work? And does
this solve your problem? Does anyone like this idea (aethestically and
pragmatically)?

  Jared.
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: proposal: standardize interface to Haskell' implementations

2006-02-20 Thread Henrik Nilsson

Dear all,

Claus Reinke wrote:

> what I have in mind are things to come, which would be quite
> different from the initial steps we could reasonably expect Haskell'
> to take. initially, a separate libary may be an acceptable start; but
> ultimately, I don't want two separate Haskell implementations shipped 
> for each installation.

>
> for the moment, I'd like the Haskell' committe to say this is useful,
> and commit to making a start, then see how far we can get.

I don't think anyone is saying a library like this would not be useful.

> at the very least, Language.Haskell needs to be expanded on, to cope
> with modules, to provide type information, and to cope
> with language extensions
> [...]
> But ultimately, there will be ramifications for future language
> definitions (how to pass from programs to representations
> and back? how to type these things? how to extend programs
> at runtime?
> [...]
> Simon M adds extensible
> data types to the list. I'm sure there's more, once we start
> looking.
>
> I find it interesting to note the the folks who claim this is
> a libary-only problem are willing to put up with lots of
> non-Haskell' hacks
> [...]
> I'd prefer to flush out these secret hacks hidden in so-called
> libraries, and to call a language feature a language feature.

Point taken. However:

  1. I'm sorry, but it seems to me that the scope of the project you
 are suggesting is just way beyond what possibly could fit
 within the Haskell' effort.

  2. It seems the language features you would need standardized to
 be able to design suitably comprehensive and flexible library
 (like extensible data types) are also way beyond what we can
 hope to cover within the Haskell' effort. At this point it is
 not even clear what these features really are.

Thus, if it at this point is can be convincingly argued that there
is a small, well-defined set of some minor extensions that, if
they were part of Haskell', would make it possible to do a substantially
better job than the present "Haskell.Language", then that case
should be made. But, in my opinion, arguing that case must not amount
to a complete library design: there just isn't time for that.

Otherwise, I'm sure a separate effort to standardize an interface to
Haskell, would yield some very valuable input to design of
the next major version of Haskell.

Yes, not doing that work as part of the Haskell' effort or in
parallel with it, might mean that Haskell' isn't as "future proof"
as it ideally should be. However, I think the next major Haskell
revision is likely to include some changes that breaks backwards
compatibility seriously anyway, so I am not too worried about that.

All the best,

/Henrik

> "Ideals are like stars. You may never be able to reach them, but you
> can navigate by them."

Not terribly accurately though, which is why they invented GPS.

:-)

--
Henrik Nilsson
School of Computer Science and Information Technology
The University of Nottingham
[EMAIL PROTECTED]


This message has been checked for viruses but the contents of an attachment
may still contain software viruses, which could damage your computer system:
you are advised to perform your own checks. Email communications with the
University of Nottingham may be monitored as permitted by UK legislation.

___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: proposal: standardize interface to Haskell' implementations

2006-02-20 Thread Claus Reinke

| (*) a standard haskell' api providing the commands of ghci/hugs
| style interactive systems would be a start, together with an
| annotated AST, parser/typer/pretty printer. more detailed
| specifications could be left for future revisions.
A reasonable suggestion, but I'm unsure what you actually have in mind.


what I have in mind are things to come, which would be quite
different from the initial steps we could reasonably expect Haskell'
to take. initially, a separate libary may be an acceptable start; but
ultimately, I don't want two separate Haskell implementations 
shipped for each installation.


for the moment, I'd like the Haskell' committe to say this is useful,
and commit to making a start, then see how far we can get.

at the very least, Language.Haskell needs to be expanded on, 
to cope with modules, to provide type information, and to cope
with language extensions [also, one might want to check whether 
SYB-style traversals, which are so useful for annotated ASTs,
are permitted within the limitation of Haskell']. but even there, 
adding and maintaining a type/module system implementation 
would be more work than exposing the existing one, and the 
same goes if we want loading/evaluation as well.


the difference between such an extended Language.Haskell and
the standardized interface I suggested is that the former is one
naive implementation of the latter. the difference between an 
extended Language.Haskell and the implementation by reflection

I had in mind is that the latter reuses the underlying Haskell
implementation to provide the same interface more efficiently
(even if that might involve translating between internal types 
and those in Language.Haskell+).


It is meta-programming because it allows Haskell programs to
operate on representations of Haskell programs. It may use
reflection to do so, if it permits Haskell programs access to
their own representations and to parts of the implementation 
they are running on. 

I don't say to do it all perfectly for Haskell', but just to make 
a start that goes beyond current Language.Haskell. For that
start, it may still be sufficient to leave most things in an library 
(**), and it doesn't have to support everything GHC's API 
does (though it does have to define implementation-independent

interfaces).

But ultimately, there will be ramifications for future language 
definitions (how to pass from programs to representations

and back? how to type these things? how to extend programs
at runtime? ... all the issues common to Template Haskell, 
hs-plugins, and type Dynamic [as done in Clean, not the 
poor man's version of Haskell]). Simon M adds extensible

data types to the list. I'm sure there's more, once we start
looking.

I find it interesting to note the the folks who claim this is
a libary-only problem are willing to put up with lots of
non-Haskell' hacks, not to mention partially functioning
work-arounds for features that belong in the language
definition (a proper type Dynamic, for instance, with
support for polymorphism, and with a way to address
the issue of representations of types originating from 
separate programs).


I'd prefer to flush out these secret hacks hidden in so-called
libraries, and to call a language feature a language feature.

Cheers,
Claus

"Ideals are like stars. You may never be able to reach them, 
but you can navigate by them."


(**) one of the attractive things about early Haskell reports
   was the combination of language definitions and libraries.

___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


RE: the MPTC Dilemma (please solve)

2006-02-20 Thread Simon Peyton-Jones
With help from Martin Sulzmann and Ross Paterson, GHC (HEAD) now
implements a richer form of functional dependencies than Mark Jones's
version, but still decidable etc.  The rules for what must appear in the
context of an instance declaration are also relaxed.  

The specification is here:

http://www.haskell.org/ghc/dist/current/docs/users_guide/type-extensions
.html#instance-decls

I think this is a step forward, and a serious candidate for Haskell'.  I
think that if you stick to these rules, everything is nailed down as
Martin so rightly says it should be.  And I am not sure we can go much
further.

Of course -fallow-undecidable-instances still lifts all restrictions,
and then all bets are off.

Many thanks to Ross and Martin.  You can try it out by downloading a GHC
snapshot (or by building from source).

Simon

| -Original Message-
| From: [EMAIL PROTECTED]
[mailto:[EMAIL PROTECTED] On Behalf Of
| isaac jones
| Sent: 11 February 2006 01:29
| To: haskell-prime@haskell.org
| Subject: the MPTC Dilemma (please solve)
| 
| I've created a wiki page and a ticket to record solutions to what I'm
| calling the "Multi Parameter Type Class Dilemma".  It's summarized
| thusly:
| 
| MultiParamTypeClasses are very useful, but mostly in the context of
| FunctionalDependencies. They are particularly used in the monad
| transformer library found in fptools. The dilemma is that functional
| dependencies are "very, very tricky" (spj). AssociatedTypes are
| promising but unproven. Without a solution, Haskell' will be somewhat
| obsolete before it gets off the ground.
| 
| I've proposed a few solutions.  Please help to discover more solutions
| and/or put them on the ticket/wiki.
| 
| Wiki page:
| http://hackage.haskell.org/trac/haskell-prime/ticket/90
| 
| Ticket:
|
http://hackage.haskell.org/trac/haskell-prime/wiki/MultiParamTypeClasses
Dilemma
| 
| 
| peace,
| 
|   isaac
| 
| 
| 
| --
| isaac jones <[EMAIL PROTECTED]>
| 
| ___
| Haskell-prime mailing list
| Haskell-prime@haskell.org
| http://haskell.org/mailman/listinfo/haskell-prime
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


RE: proposal: standardize interface to Haskell' implementations

2006-02-20 Thread Simon Marlow
On 12 February 2006 22:43, Claus Reinke wrote:

> [an innocent question on ghc-users just reminded me of another
>  missed opportunity in previous Haskell definitions: by chosing to
>  ignore the very idea of implementations, they have left tool
>  implementors in a limbo.]
> 
> these days, there is some momentum for providing Haskell with
> various tools for refactoring, documentation, profiling, tracing,
> instance generators, analyzers, pre-processors for extensions,
> editor modes, interactive interfaces (textual, graphical, visual),
> .. and even first ides, but all that is hampered by the lack of a
> standardized interface to functionality that exists in every single
> Haskell implementation: parsing, type checking, AST, (pretty
> printing,) semantic information, (evaluation).
> 
> that functionality is common to most tools, hard (and
> unneccessary) work to reimplement, and almost impossible to
> keep up to date, diverting precious man-power from small teams
> trying to provide much needed tools.
> 
> all we have at the moment is the haskell-src part of the libraries
> Language.Haskell.{Parser,Pretty,Syntax), and some Hugs- or
> GHC-specific APIs (Hugs Server API, package GHC), or other
> frontends like Programatica, etc..
> 
> compare that with Lisp, Smalltalk, SML/NJ and the like, where
> reflection support means that tool builders get a fantastic head
> start by being able to reuse available implementation functionality.

You don't say what you don't like about the existing Language.Haskell.*
libraries - on the face of it, don't they at least fulfill the
requirements for a re-usable Haskell AST, parser, and pretty-printer?
That's what they were intended to be, because we recognised the
importance of having this a long time ago.

I'll start to answer my own question: no they don't fulfill the
requirements.  Not many projects *use* Language.Haskell.*.  Why is that?
One very good reason is that the AST isn't at all extensible, and
everyone wants to extend Haskell.  Even in Haddock, I couldn't use
Language.Haskell.Syntax because I wanted to add annotations to the AST.
Later on I wanted to add GHC extensions too.  So the programmatica
project started with Language.Haskell.Syntax and made it extensible
(that's my understanding - please correct me if I got the history
wrong).  Also, we now have haskell-src-exts which is haskell-src + (some
fixed set of extensions).

So if you standardise the AST, I'm pretty sure it has to be extensible
to be useful.  It seems hard to do a good job of this: Haskell doesn't
do open-ended extensible types very well, the programatica solution is
neat but a little unweildy if you ask me.

I'm not entirely sure why you're using the term "reflection" here - I
suppose there's some overlap in that you might want to obtain the AST of
the data declaration for a particular type at runtime, but mostly I
think runtime reflection is separate from a reusable front-end.  The
Data.Generics library does a pretty good job of reflection.

Standing back a little, I think this is an ideal candidate for a
standardisation process independent of Haskell' - it's too big a task to
squeeze into the Haskell' timeframe, and there are no dependencies that
prevent it from being separately defined.  It's just a library, after
all.

Cheers,
Simon
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


RE: proposal: standardize interface to Haskell' implementations

2006-02-20 Thread Simon Peyton-Jones
| (*) a standard haskell' api providing the commands of ghci/hugs
| style interactive systems would be a start, together with an
| annotated AST, parser/typer/pretty printer. more detailed
| specifications could be left for future revisions.

Claus,

A reasonable suggestion, but I'm unsure what you actually have in mind.

I think that perhaps you mean that Haskell' should specify a (Haskell)
library through which one can compile, load, and execute Haskell
programs?  Is that right?  That is, you have in mind precisely the sort
of thing that GHC-as-a-library tries to offer?   I ask because that
isn't exactly what Java reflection, for example, offers.

If that is what you have in mind, then yes indeed, it would be great to
have such an interface specified.  But it's a big task.  The data types
involved are large, and there are lots of design choices.  We've
simplified the problem in GHC by exposing some of GHC's internal types
(e.g. Type, Class, TyCon, Id etc) which have themselves evolved over
time.  And that's before you start asking about what interfaces are
suitable for loading, renaming, typechecking, optimising etc.  

I, for one, would love it if you and others felt able to contribute to
the Haskell-as-a-library interface (i.e. what it should look like to the
client).  Whether we'd be anywhere near done for Haskell' I'm less
certain.  

There's a (GHC-specific) Wiki page for suggestions about GHC as a
library, which might be good place to start.
http://haskell.org/haskellwiki/GHC/As_a_library

Simon
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime