Re: Multiple imports on a single line

2017-02-01 Thread Malcolm Wallace
You can already write this, with only a tiny bit of syntax: module MyApp where import Data.Text; import Data.Foldable; import Control.Concurrent Whether it is good style is another matter, but all compilers will certainly accept it. Regards, Malcolm On 1 Feb 2017, at 14:18, Vassil

Re: [Haskell-cafe] MRP, 3-year-support-window, and the non-requirement of CPP

2015-10-06 Thread Malcolm Wallace
On 6 Oct 2015, at 17:47, Herbert Valerio Riedel wrote: > >> The problem by discussions is that they are done between two groups with >> quite a difference in experience. On one hand you have people like Bryan, >> who have considerable contributions to the Haskell ecosystem and much >>

Re: Monad of no `return` Proposal (MRP): Moving `return` out of `Monad`

2015-10-05 Thread Malcolm Wallace
mation about Haskell, is a powerful disincentive to continue with it. Regards, Malcolm > On 5 Oct 2015, at 10:05, Malcolm Wallace wrote: > >> I am also a strong -1 on small changes that break huge numbers of things for >> somewhat trivial benefits. >> >> Regards, &

Call for Nominations: Haskell Prime language committee

2013-02-04 Thread Malcolm Wallace
Dear Haskell lovers, The Haskell Prime process for standardisation of new versions of the Haskell language is at something of an impasse. Since the Haskell 2010 Report was issued (at the end of 2009), there has been very little momentum to formalise existing extensions and generalisations,

Re: Status of Haskell'?

2013-01-05 Thread Malcolm Wallace
On 28/12/2012, at 1:01, Ramana Kumar ram...@member.fsf.org wrote: On Wed, Dec 12, 2012 at 6:40 PM, Malcolm Wallace malcolm.wall...@me.com wrote: There is a mailing list for the members of the language committee: haskell-2011-commit...@haskell.org. Hi Malcolm, could you (or someone

Re: Status of Haskell'?

2012-12-12 Thread Malcolm Wallace
I confess that I have not had enough free time in the last two years to have been a good chair for the language committee. (Using Haskell in the real world is just too absorbing!) I think the next chair should probably be an academic, who may have more incentive to spend effort on

Re: What is a punctuation character?

2012-03-16 Thread Malcolm Wallace
no purpose to a completely overlapping category unless it is intended to relate to an earlier standard (say Haskell 1.4). I believe all Haskell Reports, even since 1.0, have specified that the language uses Unicode. If it helps to bring perspective to this discussion, it is my impression

Re: Proposal: require spaces around the dot operator

2012-02-10 Thread Malcolm Wallace
-1. I agree with John. There is no point in fiddling with the dots, until we have real experience with a new records proposal (which can be implemented entirely without using dot, at least initially). Regards, Malcolm On 10 Feb 2012, at 03:14, John Meacham wrote: I mean, it is not

Re: Please apply the comparison function given to nubBy to elements of the list in the order in which they occur in the list.

2011-09-20 Thread Malcolm Wallace
If this is a _proposal_ to change ghc's non-Report-compatible Data.List implementation to match the behaviour of the Report implementation, then count me as a +1. I think an important convention when it comes to higher order functions on lists is that to the extent which is possible, the

Re: Proposal: fix simple pattern binding and declaration group

2011-07-01 Thread Malcolm Wallace
Once you guys have reached consensus on appropriate revised wording for this issue, I'll happily apply the changes to the Haskell 2012 Report as a bugfix. Regards, Malcolm ___ Haskell-prime mailing list Haskell-prime@haskell.org

Re: TypeFamilies vs. FunctionalDependencies type-level recursion

2011-06-16 Thread Malcolm Wallace
| Is there a policy that only a proposal's owner can modify the wiki | page? Or that you have to be a member of the Haskell' committee? I'm not sure. Malcolm Wallace is chair at the moment; I'm ccing him. I have no idea: I neither set up the wiki, nor do I have any interesting admin

Re: specify call-by-need

2011-02-18 Thread Malcolm Wallace
On 16 Feb 2011, at 01:53, Scott Turner wrote: In practice, Haskell a call-by-need language. Still, software developers are not on firm ground when they run into trouble with evaluation order, because the language definition leaves this open. Is this an underspecification that should be fixed?

Re: Reform of the Monad, and Disruptive Change

2011-02-04 Thread Malcolm Wallace
On 4 Feb 2011, at 09:41, John Smith wrote: There has been a fair amount of discussion, both on this list and libraries, regarding the Monad class hierarchy. The many on the libraries list expressed support for the patch at http://hackage.haskell.org/trac/ghc/ticket/4834 , conditional on it

Re: [Haskell] Announce: ~Haskell 2011

2011-01-20 Thread Malcolm Wallace
(a) we wish to accept the NoDatatypeContexts proposal http://hackage.haskell.org/trac/haskell-prime/wiki/NoDatatypeContexts The Trac-Wiki says: What removing the datatype contexts from a source file will do is make some previously illegal programs legal. What is an example? As on the

Re: Announce: ~Haskell 2011

2011-01-08 Thread Malcolm Wallace
On 7 Jan 2011, at 22:25, Ian Lynagh wrote: Have you considered deciding about individual proposals as and when they are completed, rather than making a decision about all proposals each September? This could also avoid merge-conflicts between the report deltas for proposals that touch the

Announce: ~Haskell 2011

2011-01-07 Thread Malcolm Wallace
The Haskell Language committee has had a quiet year. Following the announcement of Haskell 2010 in Nov 2009 [1], and the publication of the 2010 Report in July 2010 [2], we found a distinct lack of complete new proposals to decide upon. As a result, the committee has made the following

Re: Functor hierarchy proposal and class system extension proposal

2011-01-02 Thread Malcolm Wallace
See also http://repetae.net/recent/out/classalias.html http://www.haskell.org//pipermail/libraries/2005-March/003494.html http://www.haskell.org//pipermail/haskell-prime/2006-April/001344.html http://www.haskell.org//pipermail/haskell-prime/2006-August/001582.html On 27 Dec

preparing for Haskell 2011

2010-08-09 Thread Malcolm Wallace
Dear all, Although the Haskell 2010 Language Report has only been published recently, it will soon be time for the Committee to make decisions on the next version, Haskell 2011. I am aiming for the committee to make decisions around the end of Sept or beginning of October 2010. Can I

Re: Propsal: NoDatatypeContexts

2010-07-20 Thread Malcolm Wallace
H98 and H2010 allow a context to be given for datatypes, e.g. the Eq a in data Eq a = Foo a = Constr a I have made a proposal to remove support for that context (ticket #139). Although I would prefer that contexts of datatypes did the right and useful thing, in the absence of a

Re: Second draft of the Haskell 2010 report available

2010-06-29 Thread Malcolm Wallace
I have now updated the libraries too. Rather than update all the library documentation manually, I (perhaps rashly) decided to make a LaTeX backend for Haddock instead, and generate the report automatically from the library source code. Perhaps I should have mentioned (before sending a

Re: Haskell 2010 libraries

2010-04-30 Thread Malcolm Wallace
3. allow packages to shadow each other, so haskell2010 shadows base. This is a tantalising possibility, but I don't have any idea what it would look like, e.g. should the client or the package provider specify shadowing? This sounds like a potentially complicated new mechanism,

Re: Haskell 2010 draft report

2010-04-30 Thread Malcolm Wallace
I'd appreciate a few more eyes over this, in particular look out for messed up typesetting as there could still be a few bugs lurking. Modified versions of this Report may also be copied and distributed for any purpose, provided that the modified version is clearly presented as such,

Haskell prime: the sequel (2011)

2010-02-22 Thread Malcolm Wallace
http://hackage.haskell.org/trac/haskell-prime The new committee for Haskell language standardisation has been appointed, based on public nominations. I am the new chair. http://hackage.haskell.org/trac/haskell-prime/wiki/Committee In case you missed it, the previous committee

Re: Nominations for the Haskell 2011 committee

2009-12-20 Thread Malcolm Wallace
To nominate someone (which may be yourself), send a message to haskell-prime@haskell.org . Please give reasons for your nomination. I would like to nominate Neil Mitchell for the Haskell Prime committee. He falls into the categories of commercial user, and open-source tool writer. He has been

Re: Standarize GHC.Prim.Any

2009-08-18 Thread Malcolm Wallace
Also, can/do all compilers that implement unsafeCoerce implement a safe Any? Hugs can do it with just data Any = Ignored I believe, not sure about nhc, yhc or jhc... nhc98 and yhc do not implement the Any type. unsafeCoerce is easily implemented without it. Regards, Malcolm

Re: bug in language definition (strictness)

2009-08-07 Thread Malcolm Wallace
Yet I think it would be valid to say that seq can turn a non-terminating (exceptioning) program into a terminating one. Do you have an example of that? Sure. foldl (+) 0 [1..1000] :: Integer *** Exception: stack overflow foldl' (+) 0 [1..1000] :: Integer

Re: bug in language definition (strictness)

2009-08-07 Thread Malcolm Wallace
If, as I understand it, you are relying on the fact that seq's first argument is evaluted before its second, then you really want pseq rather than seq. In GHC we provide a way to do what you want (pseq), I'm just not convinced it should be the required behaviour of seq. Whilst looking

Re: NoMonomorphismRestriction

2009-08-07 Thread Malcolm Wallace
On 6 Aug 2009, at 12:18, Simon Peyton-Jones wrote: The paper makes the (somewhat radical) case for not generalising local bindings at all; which would at a stroke remove most of the issues of the MR. (We'd still need to think about the top level.) Only the other day I was writing some

Re: bug in language definition (strictness)

2009-08-06 Thread Malcolm Wallace
What semantics would you like Haskell to have, in which (x `seq` y `seq` e) and (y `seq` x `seq` e) are not equal? I can easily imagine that (x `seq` y `seq` e) might have *two* semantic denotations: bottom (Exception: stack overflow), and e. And I would like to be able to choose which

Re: Proposal: change to qualified operator syntax

2009-07-14 Thread Malcolm Wallace
left section right section prefix unqualified (+ 1) (1 +) (+) Haskell 98 (M.+ 1) (1 M.+) (M.+) proposed (`M.(+)` 1) (1 `M.(+)`) M.(+) or(*) (M.(+) 1) (flip M.(+) 1) The last line is not correct. (M.(+) 1) captures the first

Re: Haskell 2010: libraries

2009-07-14 Thread Malcolm Wallace
A natural language consists of a vocabulary of words, as well as a grammar for stringing them together. If we omit the common basic libraries from the language definition, then are we implicitly reducing the common vocabulary, and encouraging dialects to appear? If I see the function

Re: what about moving the record system to an addendum?

2009-07-07 Thread Malcolm Wallace
On 7 Jul 2009, at 02:28, John Meacham wrote: Haskell currently doesn't _have_ a record syntax (I think it was always a misnomer to call it that) it has 'labeled fields'. ... and a reworking of the standard to not refer to the current system as a 'record syntax' but rather a 'labeled

Re: Announcing the new Haskell Prime process, and Haskell 2010

2009-07-07 Thread Malcolm Wallace
i can't understand. does this list supposed to be full list of changes in haskell'? this is a provisional list of features that the Haskell' committee thinks would be feasible to include in a 2010 revision of the Haskell standard. And just to add, the new standardisation process means that

Re: Proposal: Deprecate ExistentialQuantification

2009-06-27 Thread Malcolm Wallace
I would hereby like to propose that the ExistentialQuantification extension is deprecated. It is worth pointing out that all current Haskell implementations (to my knowledge) have ExistentialQuantification, whilst there is only one Haskell implementation that has the proposed replacement

Re: RFC: qualified vs unqualified names in defining instance methods

2008-04-25 Thread Malcolm Wallace
It is illegal to give a binding for a class method that is not in scope, but thename under which it is in scope is immaterial; in particular, it may be aqualified name. I believe this was a change introduced in H'98 to tidy up the language. Previously, if a class was imported

patch applied (haskell-prime-report): typo in section 3.17.2, rule 8, for pattern-matching n+k

2008-03-17 Thread Malcolm Wallace
Mon Mar 17 03:45:08 PDT 2008 [EMAIL PROTECTED] * typo in section 3.17.2, rule 8, for pattern-matching n+k M ./report/exps.verb -2 +2 ___ Haskell-prime mailing list Haskell-prime@haskell.org http://www.haskell.org/mailman/listinfo/haskell-prime

patch applied (haskell-prime-report): very minor typos in section 5.6

2008-03-17 Thread Malcolm Wallace
Mon Mar 17 06:12:29 PDT 2008 [EMAIL PROTECTED] * very minor typos in section 5.6 M ./report/modules.verb -2 +2 ___ Haskell-prime mailing list Haskell-prime@haskell.org http://www.haskell.org/mailman/listinfo/haskell-prime

Re: do-and-if-then-else modification

2007-02-19 Thread Malcolm Wallace
isaac jones [EMAIL PROTECTED] wrote: Iavor and I just made the trivial modification for DoAndIfThenElse Any comments on this modification? How do people feel about the suggestion that we do it for case statements as well? I'm happy to allow the change for if-then-else. The need for extra

Re: rank-2 vs. arbitrary rank types

2007-02-05 Thread Malcolm Wallace
Iavor Diatchki [EMAIL PROTECTED] wrote: I don't think that the rank-N system is any more expressive then the rank-2 one. The reason is that by placing a polymorphic value in a datatype we can decrese its rank. In this way we can reduce a program of any rank to just rank-2. The same

Re: help from the community?

2007-02-02 Thread Malcolm Wallace
Douglas Philips [EMAIL PROTECTED] wrote: .to fark around with that stoopid ass ... Pisses off users ... domineering compiler writer can feel smug 'bout 'mself. Feh. Feh^2. Hey, man, take a chill pill.

Re: List syntax (was: Re: help from the community?)

2007-02-02 Thread Malcolm Wallace
Douglas Philips [EMAIL PROTECTED] wrote: What would be the proper way to propose that: | ( exp1 , ... , expk ) (tuple, k=2) | [ exp1 , ... , expk ] (list, k=1) be amended to: | ( exp1 , ... , expk [ , ] ) (tuple, k=2) | [ exp1 , ... , expk [

Re: help from the community?

2007-02-01 Thread Malcolm Wallace
On 1 Feb 2007, at 21:31, Jacques Carette wrote: Stephanie Weirich wrote: I don't think we want to allow types like: forall . Int or forall a b. Int These types are mostly bugs. Furthermore, rejecting them doesn't limit expressiveness: If you restrict yourself to programs

Re: help from the community?

2007-01-26 Thread Malcolm Wallace
isaac jones [EMAIL PROTECTED] wrote: http://hackage.haskell.org/trac/haskell-prime/ticket/57 Does anyone have any feedback on this work? Yes, here are my thoughts. PROPOSAL: adopt GHC's convention and treat 'forall' specially in types but allow it to be used in value declarations.

Re: defaults

2007-01-16 Thread Malcolm Wallace
Simon Marlow [EMAIL PROTECTED] wrote: If so, then I offer a counter example: toRational pi If these two points are valid, then I think the slight loss of backward compatibility is acceptable? I spotted the problem because it looks (to me) like the current Haskell 98 rule is

Re: defaults

2007-01-15 Thread Malcolm Wallace
Simon Marlow [EMAIL PROTECTED] wrote: Is your proposal supposed to be backwards compatible with Haskell 98 for programs that don't have default declarations? Yes, it is supposed to be backwards compatible. If so, then I offer a counter example: toRational pi will default pi to Double

patch applied (haskell-prime-report): Change front matter to say quot; Haskell Primequot; rather than quot; Haskell 98quot; .

2007-01-08 Thread Malcolm Wallace
Mon Jan 8 07:06:32 PST 2007 [EMAIL PROTECTED] * Change front matter to say Haskell Prime rather than Haskell 98. M ./report/haskell.verb -5 +6 M ./report/intro.verb -1 +1 M ./report/preface-jfp.verb -53 +68 ___ Haskell-prime mailing list

Re: Proposal for stand-alone deriving declarations?

2006-11-01 Thread Malcolm Wallace
Brian Smith [EMAIL PROTECTED] writes: http://haskell.org/haskellwiki/GHC/StandAloneDeriving Basically, the syntax for instances and derived instances would be identical, but derived instances would just omit the where clause, while non-derived instances would need the where

Re: seq vs. pseq

2006-10-27 Thread Malcolm Wallace
Simon Marlow [EMAIL PROTECTED] wrote: The difference is subtle. The semantics of seq and pseq are identical; however, GHC can see that seq is strict in both its arguments and hence could choose to evaluate them in either order, whereas pseq is only strict in its first argument as far as

Re: (Pattern) Guards in lambdas

2006-10-18 Thread Malcolm Wallace
Claus Reinke [EMAIL PROTECTED] wrote: since Pattern Guards appear to be popular with the committee, I suggest to revisit the decision to drop guards from lambdas: suggestion: undo removal of guards from lambdas, especially (but not only) if pattern guards make it into the language. See the

Re: Pattern matching order for records

2006-10-13 Thread Malcolm Wallace
Ian Lynagh [EMAIL PROTECTED] wrote: Has clarifying the pattern matching order for records as described in http://hackage.haskell.org/trac/ghc/ticket/246 been discussed for haskell'? I couldn't see it on the proposals list. Perhaps because this has already been fixed in the errata to the

Re: Regarding Class Aliases

2006-05-23 Thread Malcolm Wallace
Christophe Poucet [EMAIL PROTECTED] wrote: Class Aliases. I have looked at the ticket and right now it's marked as a low priority with low probability of entering the standard. I think class aliases might be a nice idea too. But we don't have any concrete experience with implementations that

Re: preemptive vs cooperative: attempt at formalization

2006-04-12 Thread Malcolm Wallace
John Meacham [EMAIL PROTECTED] wrote: In a concurrent implementation, a thread performing an infinite loop with no IO or interaction with the outside world can potentially stall switching to another thread forever, in FP, we usually denote an infinite loop by _|_. so I think the first

Re: preemptive vs cooperative: attempt at formalization

2006-04-12 Thread Malcolm Wallace
Simon Marlow [EMAIL PROTECTED] wrote: By infinite loop, you mean both non-terminating, and non-productive. A non-terminating but productive pure computation (e.g. ones = 1:ones) is not necessarily a problem. That's slightly odd terminology. ones = 1:ones is definitely terminating.

FD use cases (was Re: postponing discussion on exceptions and deepSeq)

2006-04-12 Thread Malcolm Wallace
isaac jones [EMAIL PROTECTED] wrote: Ross has asked for use cases for functional dependencies and so far has only two replies. Surely there are those on this list who have use of functional dependencies? Personally, I have never used FDs, but I recall some discussion we had in the Hat

Re: FFI, safe vs unsafe

2006-03-30 Thread Malcolm Wallace
Simon Marlow [EMAIL PROTECTED] wrote: I thought yhc supported unboxed values, so a loop like count 0 = 0 count n = count (n - 1) count 10 could block the runtime (assuming it was properly unboxed by the compiler) since it never calls back into it and is just a straight

concurrency (was Re: important news: refocusing discussion)

2006-03-28 Thread Malcolm Wallace
Tomasz Zielonka [EMAIL PROTECTED] wrote: It may be relevant for this discussion: I believe I reimplemented STM, including retry and orElse, on top of old GHC's concurrency primitives. http://www.uncurry.com/repos/FakeSTM/ Perhaps it could serve as a drop-in replacement for STM in

concurrency (was Re: important news: refocusing discussion)

2006-03-28 Thread Malcolm Wallace
Simon Marlow [EMAIL PROTECTED] wrote: The portable interface could be Control.Concurrent.MVar, perhaps. I don't really understand the problem, maybe I'm missing something. I thought the idea would be that a thread-safe library would simply use MVar instead of IORef. I was misled by

Re: Concurrency (was: RE: Re[2]: important news: refocusing discussion)

2006-03-28 Thread Malcolm Wallace
Simon Marlow [EMAIL PROTECTED] wrote: (a) we're going to standardise concurrency anyway Well, but that only begs the question, what *kind* of concurrency are we going to standardise on? e.g. Will we admit all variations of scheduling (co-operative, time-slice, and pre-emptive)? (b) it is

Re: important news: refocusing discussion

2006-03-27 Thread Malcolm Wallace
John Goerzen [EMAIL PROTECTED] wrote: On Fri, Mar 24, 2006 at 11:07:53AM +, Malcolm Wallace wrote: I assume that since a non-concurrent implementation has only one thread, that thread will be trying to MVar-synchronise with something that does not exist, and hence

Re: Ranges and the Enum class

2006-03-21 Thread Malcolm Wallace
Wolfgang Jeltsch [EMAIL PROTECTED] writes: Also, toEnum and fromEnum would make more sense mapping from and to Integer. Why do we need toEnum and fromEnum at all? As far as I know, they are merely there to help people implement things like enumFrom. They are often useful for writing

Re: Infix expressions

2006-03-15 Thread Malcolm Wallace
[EMAIL PROTECTED] (Donald Bruce Stewart) writes: Yes, this is _exactly_ the kind of thing to add to the Idioms page of the wiki, here: http://www.haskell.org/haskellwiki/Category:Idioms So if anyone knows of an interesting Haskell trick, and wants to write about it, add a page! It is

Re: the dreaded offside rule

2006-03-10 Thread Malcolm Wallace
Simon Marlow [EMAIL PROTECTED] wrote: Here's another couple that just occurred to me: f x | let y = x = y f x = case x of _ | let y = x - y granted these are unlikely to occur in practice. Are these Haskell'98? I'm afraid I don't understand how a let binding (without in) can occur

Re: Keep the present Haskell record system!

2006-03-01 Thread Malcolm Wallace
Ross Paterson [EMAIL PROTECTED] wrote: On Wed, Mar 01, 2006 at 08:26:14AM +, Henrik Nilsson wrote: I'm increasingly convinced that the records should be left alone for Haskell', possibly modulo some minor tweaks to polish the system. Yes, no alternative candidate is available

Re: Export lists in modules

2006-02-28 Thread Malcolm Wallace
Johannes Waldmann [EMAIL PROTECTED] wrote: For reference, in Java, ... there's nice syntactic sugar for looping over collections: CollectionE c; for (E item : c) { ... } I'd say this is an example of moving away from a left-biased representation, or at least freeing the programmer from

Re: Export lists in modules

2006-02-28 Thread Malcolm Wallace
Johannes Waldmann [EMAIL PROTECTED] wrote: In Haskell, this is called 'fmap'. :-) OK, then show me an instance Functor Set so that I can use it :-) instance Function Set where fmap = Data.Set.mapMonotonic Ok, so this introduces a precondition on the function being mapped, so there is

Re: instance Functor Set, was: Re: Export lists in modules

2006-02-28 Thread Malcolm Wallace
But if contexts-on-datatypes worked correctly, data Set a = Ord a = then even the real map from Data.Set: map :: (Ord a, Ord b) = (a - b) - Set a - Set b could be an instance method of Functor. I'd love that. But I don't quite understand: do you think this

Re: [Haskell'-private] pragmas and annotations (RE: the record system)

2006-02-28 Thread Malcolm Wallace
Simon Marlow [EMAIL PROTECTED] wrote: How does ENCODING work for a UTF-16 file, for example? We don't know the file is UTF-16 until we read the ENCODING pragma, and we can't read the ENCODING pragma because it's in UTF-16. Use the same type of heuristic as XML uses (for instance). * If

Re: Export lists in modules

2006-02-23 Thread Malcolm Wallace
Ketil Malde [EMAIL PROTECTED] wrote: I would solve this problem by reducing the Prelude to just a core. List function could go, for example, (mostly) into Data.List. If this means that you must import Data.List almost everywhere, this won't change anything - only add yet another import

Re: Export lists in modules

2006-02-23 Thread Malcolm Wallace
Simon Marlow [EMAIL PROTECTED] wrote: However, I would be equally happy to combine type/newtype/data into a single keyword for exports. for the record, I am in favour of tagging export specifiers with 'class' or 'type' (using 'type' for all type constructors, in light of yours and

Re: Re[2]: Export lists in modules

2006-02-23 Thread Malcolm Wallace
Bulat Ziganshin [EMAIL PROTECTED] wrote: MW With my proposal, you would simply replace the MW implicit import Prelude with an explicit import MW Prelude.Standard import Prelude ($) can't solve this problem? One of the problems with the current mechanism for overriding Prelude definitions,

Re: Export lists in modules

2006-02-22 Thread Malcolm Wallace
John Meacham [EMAIL PROTECTED] wrote: Malcolm Wallace wrote: There is also the issue that we might adopt the proposal to allow (and perhaps eventually, to require) type signatures on export lists. All I have to say is please, no to the requiring part that is. I don't seriously propose

Re: Export lists in modules

2006-02-22 Thread Malcolm Wallace
Johannes Waldmann [EMAIL PROTECTED] wrote: Sounds like the perfect example to illustrate the point that information shouldn't be doubled in the first place. Yes, I suppose one could argue that. Can you say why you want the type in the export list? As a compact description of the module

Re: Export lists in modules

2006-02-22 Thread Malcolm Wallace
Simon Peyton-Jones [EMAIL PROTECTED] wrote: | I don't seriously propose for haskell-prime that signatures should | be required on exports. Just permitting them would be a large and | useful step up already. If this is to be a serious proposal, someone had better think what to do about

Re: Pragmas for FFI imports

2006-02-21 Thread Malcolm Wallace
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

Re: Export lists in modules

2006-02-21 Thread Malcolm Wallace
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 believe some people (perhaps

Re: Re[2]: Tuple-like constructors

2006-02-08 Thread Malcolm Wallace
Robert Dockins [EMAIL PROTECTED] writes: instance (Bin a,Bin b,Bin c,Bin d) = Bin (a,b,c,d) See the problem? Sooner or later (probably sooner) I'll get tired of typing. I have to write down an 'instance' declaration for each value of n. Clearly this can't generalize to all n. There

Re: The dreaded M-R

2006-01-31 Thread Malcolm Wallace
Simon Marlow [EMAIL PROTECTED] writes: Given the new evidence that it's actually rather hard to demonstrate any performance loss in the absence of the M-R with GHC, I'm attracted to the option of removing it in favour of a warning. As another data point, today for the first time I received an

Re: separate class and type namespace

2006-01-31 Thread Malcolm Wallace
Marcin 'Qrczak' Kowalczyk [EMAIL PROTECTED] writes: I've always liked the idea of saying 'class C' or 'type T' in import/export lists. Type signatures too should be allowed in export lists. Both ideas already noted at http://haskell.galois.com/trac/haskell-prime/wiki/ModuleSystem

Re: The dreaded M-R

2006-01-30 Thread Malcolm Wallace
[EMAIL PROTECTED] writes: Nhc didn't use to implement the M-R (maybe it does now). When porting code to nhc this caused a few code changes. Perhaps 10 lines out of 1 when I tried the Bluespec compiler. So my gut feeling is that the M-R is a rare beast in practise. I can confirm that

Re: The dreaded M-R

2006-01-26 Thread Malcolm Wallace
Simon Marlow [EMAIL PROTECTED] writes: On 26 January 2006 09:59, John Hughes wrote: The solution I favour is simply to use *different syntax* for the two forms of binding, I wonder if there's an alternative solution along these lines: - We use ParialTypeSignatures to make bindings