Re: Meta-point: backward compatibility

2008-04-30 Thread Aaron Denney
On 2008-04-30, Ross Paterson <[EMAIL PROTECTED]> wrote:
> On Thu, Apr 24, 2008 at 08:18:10PM +0000, Aaron Denney wrote:
>> And there is a lot that clearly isn't battle tested in a reasonable new
>> form, though the current practice is widely agreed upon to be broken.
>> Examples include all monads having fail, rather than only those in a
>> subclass, monad not being a subclass of functor, and the whole numeric
>> hierarchy issue (which I don't think can be properly designed unless we
>> know whether it's going to be FDs or ATs, though, of course, designing
>> it for either would provide valuable experience for the limitations
>> of both),
>
> I don't think any of these need involve multi-parameter type classes
> (we don't need vector spaces in the Prelude), but they're often presented
> as use cases for things like class aliases.  Even then, the numeric
> hierarchy is probably easier to fix that the others: one can define a
> finer-grain hierarchy with the existing classes as a facade, and leave
> clients untouched.  The change would be felt by the minority defining
> instances of numeric classes, but they are exactly the people who find
> the present hierarchy inadequate.

Class aliases (or the ability to add superclasses) would certainly help
in letting many of these things be more easily tested.

I suppose we don't need vector spaces.  Nor do we need rationals,
complex numbers, or even arbitrarily large integers.  Nevertheless,
there is a huge benefit to having the interfaces for them there.

-- 
Aaron Denney
-><-

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


Re: Meta-point: backward compatibility

2008-04-24 Thread Aaron Denney
On 2008-04-23, Simon Marlow <[EMAIL PROTECTED]> wrote:
> Johan Tibell wrote:
>> An interesting question. What is the goal of Haskell'? Is it to, like
>> Python 3000, fix warts in the language in an (somewhat) incompatible
>> way or is it to just standardize current practice? I think we need
>> both, I just don't know which of the two Haskell' is.
>
> The stated goal is still for Haskell' to be a language that is stable 
> and relevant for large-scale development for several years to come.
>
> It is mainly a consolidation effort: that is, we aim to standardise 
> existing practice in the form of language extensions that are currently 
> implemented and widely used.  Having said that, the standardisation 
> process gives us the opportunity to critically assess the design of 
> these extensions, and the design of the system as a whole, and as a 
> result we may wish to make changes in order that the resulting language 
> does not have inconsistencies, design flaws, or critical omissions.

Given a fairly limited goal of "consolidating current practice", not
much should change.  And this is a very useful thing to do.  The problem
is that many of us don't see any opportunity for large change after
this.  We expect any changes in the hypothetical Haskell 2 (or 201x) to
be resisted tooth and nail by the larger crowd as Haskell grows.  And
there is a lot that clearly isn't battle tested in a reasonable new
form, though the current practice is widely agreed upon to be broken.
Examples include all monads having fail, rather than only those in a
subclass, monad not being a subclass of functor, and the whole numeric
hierarchy issue (which I don't think can be properly designed unless we
know whether it's going to be FDs or ATs, though, of course, designing
it for either would provide valuable experience for the limitations of
both),  Many of these are "mere" library changes, but library changes
that are nearly as fundamental as language changes, because of how tied
in the prelude is currently.  It's still not entirely straightforward to
replace the prelude with a custom one, which makes it harder to test
some of these changes in real world use.  All of these factors combine
to make the ones who get annoyed with these problems to want to shoehorn
in changes right now.

-- 
Aaron Denney
-><-

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


Re: patch applied (haskell-prime-status): add ""Make $ left associative, like application"

2008-04-23 Thread Aaron Denney
On 2008-04-23, Sittampalam, Ganesh <[EMAIL PROTECTED]> wrote:
> There's plenty of code out there that doesn't have the benefit
> of a vigilant user community ready to spring into action. For
> example, Credit Suisse has several tens of thousands of lines of 
> code written by internal users who are not Haskell experts, and
> it would be rather hard to explain to them that they needed to 
> go through it all and fix it.

What makes them need to update to Haskell' instead of sticking with
Haskell '98?

-- 
Aaron Denney
-><-

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


Re: patch applied (haskell-prime-status): add ""Make $ left associative, like application"

2008-04-22 Thread Aaron Denney
On 2008-04-22, Simon Marlow <[EMAIL PROTECTED]> wrote:
> Chris Smith wrote:
>> I know it would break 
>> nearly every single piece of Haskell code I've ever written.  As such, 
>> I'm biased toward thinking it's an extremely bad idea.
>
> Absolutely.  Given that, we'd need a *very* good reason to make the change.

Surely we don't expect the majority of Haskell code to work unchanged as
Haskell' code?

-- 
Aaron Denney
-><-

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


Re: Some clarity please!

2008-03-13 Thread Aaron Denney
On 2008-03-13, Ketil Malde <[EMAIL PROTECTED]> wrote:
> Aaron Denney <[EMAIL PROTECTED]> writes:
>
>> Well, the way the report specifies that max's default definition
>> is.  I'd actually favor making that not an instance function at
>> all, and instead have max and min be external functions.
>
> If you permit a naïve question:
>
> Prelude> :i Ord
> class (Eq a) => Ord a where
>   compare :: a -> a -> Ordering
>   (<) :: a -> a -> Bool
>   (>=) :: a -> a -> Bool
>   (>) :: a -> a -> Bool
>   (<=) :: a -> a -> Bool
>   max :: a -> a -> a
>   min :: a -> a -> a
>
> ..while all functions could be easily derived from 'compare'.  Or from
> the Eq instance's (==) and (<), say.
>
> What is the reason for this?  Efficiency?  (Which couldn't be handled
> equally well by RULES?)  Otherwise, it looks like an invitation for
> writing inconsistent instances.

My impression (which may not be entirely accurate) is not primarily for
efficiency (though that is one reason), but for ease of implementation.

It may be easier in some cases to think through the various cases of
compare, or to just figure out what (<=) is.  Either of these is
sufficient (perhaps in combination with (==) from the superclass).

You can write things so that any of (<), (<=), (>), or (>=) are
sufficient, but for writing the default compare, it's easiest to know
ahead of time which you are basing it on, so definitions don't get
circular.

max and min seem to have neither justification going for them, although
I suppose it's technically possible to write compare in terms of them
and (==).

I don't think GHC's RULES were around when Haskell 98 was being formalized,
nor is it clear that one compiler's method should let other efficiency
concerns go by the wayside.

Of course, it would be nice to be able to write (==) in terms of
compare.  While doable manually there's no way to default it to that
"smartly".  There are similar issues with Functor and Monad.  ISTR
some discussion about this on the list previously.

-- 
Aaron Denney
-><-

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


Re: Some clarity please! (was Re: Re: (flawed?) benchmark : sort)

2008-03-13 Thread Aaron Denney
beyed.  They
are purely "social" interfaces, in that the community of code writers
determines the real meaning, and what can be depended on.  The community
absolutely should come to a consensus of what these meanings are and
document them better than they are currently.

Currently, if you write code assuming a stricter meaning of Eq a, the
consequences are:
(a) it's easier for you to write code
(b) it's harder for others to interoperate with your code and use it.

Generally, you're the one that gets to make this trade off, because
you're writing the code.  Whether someone else uses your code, or
others', or writes their own is then their own trade off.  Because,
indeed, many many types inhabiting Eq do obey observational equality,
the consequences of (b) may be minor.

With regards to Haskell 98, my best guess is that some of the committee
members thought hard about the code so that Eq a would usually work for
any equivalence class, and others took it to mean observational equality
and wrote prose with this understanding.

-- 
Aaron Denney
-><-

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


Re: [Haskell-cafe] global variables

2007-05-24 Thread Aaron Denney
On 2007-05-24, David House wrote:
> On 24/05/07, Adrian Hey <[EMAIL PROTECTED]> wrote:
>> Or even at compile time (which is why I think it's reasonable to
>> regard operations like newIORef etc.. as not really being "IO"
>> operations at all).
>
> You can allocate heap space at compile time? (Well, I guess you could,
> but that wouldn't still be usable at run time...) I imagine newIORef
> as mallocing() some room, then returning a pointer to that memory.
> That doesn't seem like something that could be done at compile time.

You can allocate bss or data space at compile time for the executable
you are compiling.  (Well, if you read compile as compile and link.
It's a bit fuzzy.)

-- 
Aaron Denney
-><-

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


Re: Relax the restriction on Bounded derivation

2007-04-18 Thread Aaron Denney
On 2007-04-18, Isaac Dupree <[EMAIL PROTECTED]> wrote:
> (Float and Double *aren't* in Bounded. Then again, Haskell98 doesn't
> require them to contain non-_|_ values of +-infinity.)

And they're only in Enum to support the [a..b] syntax, whose semantics
can't really sanely be supported for Float and Double anyways.

> Furthermore, there are bounded things that aren't enumerable anyway (I
> think) (such as some lattices), so it would be odd to add that
> restriction just because the type might also be in Prelude.Enum.

I'd really like to see one.  Unless you're just talking about
a set with a partial order, in which case, yes, many are bounded.
e.g. reals in [0, 1], as when being used for probabilities.

> Rather, I would ask "Must any inhabitant of a type in Enum be reachable
> by pred or succ from an arbitrary inhabitant of the type?"

That would make sense to me (when restricted to non-bottom inhabitants),
and is essentially the objection that many have to Float and Double
being in Enum.

> For example,
> I could declare an instance of Enum that contradicted that:
> data Something = Some Integer | Another Integer
> where pred and succ always stayed within the same constructor, and for
> fromEnum/toEnum I would just find some way to encode some common (i.e.
> relatively small magnitude, just as the usual instance Enum Integer is
> limited this way) values of Something into an Int. Or are
> fromEnum/toEnum supposed to obey some sort of properties, when they are
> defined, relative to the rest of the methods? I would guess not, given
> the comment
> - -- NOTE: these default methods only make sense for types
> - --   that map injectively into Int using fromEnum
> - --  and toEnum.
> (hugs: fromEnum (2.6 :: Double) ---> 2)
>
>
> Cheers,
> Isaac

The default implementation for the class assumes 
    fromEnuw (succ x) = 1 + fromEnum x
and similar things.

That's a pretty strong argument that all types should obey that.

-- 
Aaron Denney
-><-

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


Re: digit groups

2006-10-30 Thread Aaron Denney
On 2006-10-26, Jon Fairbairn <[EMAIL PROTECTED]> wrote:
> On 2006-10-25 at 20:57-0000 Aaron Denney wrote:
>> On 2006-10-25, Jon Fairbairn <[EMAIL PROTECTED]> wrote:
>> > No. A small alteration to the lexical syntax for the sake of
>> > improved readability seems perfectly justifiable as long as
>> > it doesn't make the lexical syntax /significantly/ more
>> > complicated or harder to learn.
>> 
>> Sure.  But some of us don't find it terribly readable. 
>
> I'm not sure what you are saying here. Assessing readability
> by introspection is terribly unreliable. Unfamiliarity with
> the presentation of numbers with underlines is likely to
> make them feel a bit awkward to begin with, but habituation
> is likely to change that.

Fair enough, I don't actually find it less readable, merely quite ugly.
I might indeed get used to it.

>> I think the ~~ operator hack gets 90% of the "benefit" for
>> those who want it.
>
> I thought my earlier message adequately demonstrated that it
> does /not/.

You demonstrated some corner cases that weren't convincing at all.

> Another case: if you change “square
> 123479010987” to “square 123_479_010_987” to improve
> readability it still means the same thing. If you change it
> to “square 123~~479~~010~~987” it doesn't.

This is a bit more convincing.

-- 
Aaron Denney
-><-

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


Re: digit groups

2006-10-25 Thread Aaron Denney
On 2006-10-25, Jon Fairbairn <[EMAIL PROTECTED]> wrote:
> No. A small alteration to the lexical syntax for the sake of
> improved readability seems perfectly justifiable as long as
> it doesn't make the lexical syntax /significantly/ more
> complicated or harder to learn.

Sure.  But some of us don't find it terribly readable.  I think the ~~
operator hack gets 90% of the "benefit" for those who want it.

> although my preference would be something a bit more
> restrictive, requiring numbers to have groups of the same
> number of digits after each “_” and beginning with a shorter
> group (ie 12_000_000 and 1200_ would be valid but
> 1247_000 would not). I'm not wedded to this requirement (and
> it would take a more sophisticated grammar to formalise).

The only reason to put it in the lexer/parser is to avoid misleading cases,
which needs thas additional restriction, or something similar, like
always 3 for decimal, 4 for hex, 3 for oct, or whatever.

-- 
Aaron Denney
-><-

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


Re: Small note regarding the mailing list

2006-09-02 Thread Aaron Denney
On 2006-09-02, Philippa Cowderoy <[EMAIL PROTECTED]> wrote:
> On Sat, 2 Sep 2006, Aaron Denney wrote:
>
>> On 2006-09-02, Philippa Cowderoy <[EMAIL PROTECTED]> wrote:
>> > On Sat, 2 Sep 2006, isaac jones wrote:
>> >
>> >> On Tue, 2006-08-29 at 14:04 +0200, Christophe Poucet wrote:
>> >> > Hello,
>> >> > 
>> >> > Just a small request.  Would it be feasible to tag the Haskell-prime
>> >> > list in a similar manner as Haskell-cafe?
>> >> 
>> >> I'd rather not.  If you want to be able to filter, you can use the
>> >> "Sender" field which will always be:
>> >> Sender: [EMAIL PROTECTED]
>> >> 
>> >
>> > This isn't really enough if you're scan-reading a pile of stuff - are 
>> > there any particularly good reasons to avoid the tags? They're pretty much 
>> > standard practice.
>> 
>> They take away valuable space that can be used for informative messages.
>> 
>
> I rarely see a subject I can't read the whole of in a single line anyway, 
> though.

Well, I've seen it happen on occasion.

>> If you want to filter it out, don't do it by hand, that's what computers
>> are for.
>> 
>
> That's not the problem, though. The occasional problem is not accidentally 
> thinking "oh, that's spam" and deleting a post because you don't recognise 
> the poster and the subject line looks vaguely spamlike. And the spammers 
> have found ways of dealing with bayesian filters by now. If I whitelist 
> and then scan through a spam folder once in a while that makes things even 
> worse, because the proportion of spam in the spam folder is that much 
> higher.

I misspoke -- I shouldn't have said "out".  Send mailing list
traffic to seperate mail folders, with seperate new mail indicators, and
everything is golden.

-- 
Aaron Denney
-><-

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


Re: Small note regarding the mailing list

2006-09-02 Thread Aaron Denney
On 2006-09-02, Philippa Cowderoy <[EMAIL PROTECTED]> wrote:
> On Sat, 2 Sep 2006, isaac jones wrote:
>
>> On Tue, 2006-08-29 at 14:04 +0200, Christophe Poucet wrote:
>> > Hello,
>> > 
>> > Just a small request.  Would it be feasible to tag the Haskell-prime
>> > list in a similar manner as Haskell-cafe?
>> 
>> I'd rather not.  If you want to be able to filter, you can use the
>> "Sender" field which will always be:
>> Sender: [EMAIL PROTECTED]
>> 
>
> This isn't really enough if you're scan-reading a pile of stuff - are 
> there any particularly good reasons to avoid the tags? They're pretty much 
> standard practice.

They take away valuable space that can be used for informative messages.

If you want to filter it out, don't do it by hand, that's what computers
are for.

-- 
Aaron Denney
-><-

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


Re: map and fmap

2006-08-20 Thread Aaron Denney
On 2006-08-20, John Hughes <[EMAIL PROTECTED]> wrote:
>
> From: "Jon Fairbairn" <[EMAIL PROTECTED]>
>
>> To
>> reinforce what Aaron said, if a programme works now, it'll
>> still work if map suddenly means fmap.
>
> Well, this isn't quite true, is it? Here's an example:
>
> class Foldable f where
>   fold :: (a -> a -> a) -> a -> f a -> a
>
> instance Foldable [] where
>   fold = foldr
>
> example = fold (+) 0 (map (+1) (return 2))
>
> example has the value 3 (of course), but if you replace map by fmap then the 
> code no longer compiles.

Solely due to the compiler no longer seeing that list is the only
intermediate type allowed.  But you have to admit this code is a bit
forced.  People won't be combining things quite this way, and will be
passing in values rather than bare returns.

> In any case, I'm dubious about this as a criterion. I would guess that the 
> majority if compiler runs for beginners (and perhaps for the rest of us 
> too!) end in a type error, not a successful compilation, so arguably the 
> quality of error messages when a type-check fails is more important than 
> which programs compile.

Right, like I said, we need to work on better error messages.

-- 
Aaron Denney
-><-

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


Re: map and fmap

2006-08-18 Thread Aaron Denney
On 2006-08-18, John Hughes <[EMAIL PROTECTED]> wrote:
> Jon Fairbairn <[EMAIL PROTECTED]>
>> A reasonable choice (forestalling the objection that using
>> List.map, listMap or mapList would be too distracting for
>> students) would be
>>
>>   lmap:: (t -> t') -> [t] -> [t']
>>   map:: Functor f => (t -> t') -> f t -> f t'
>>
>
> I'd prefer mapList to lmap, to be honest--at least the connection between 
> the name
> and the type is clear. But remember, this would at a stroke make Haskell'
> incompatible with all existing Haskell textbooks. Even if publishers brought
> out new editions, even if we told students to buy them, there are many, many
> second hand books in circulation, and it would be years before one could 
> rely
> on students having Haskell' books. All that time, students would write map
> instead of mapList because that's what the book says, and get stuck with
> incomprehensible error messages. Is it really worth an incompatible change
> in the library functions used by all beginners, just to rename fmap to map?
> It seems to me that the gain from a change is very small, and the cost 
> considerable.

But list is a functor, so it should work.  They just get harder error
messages, when their programs are wrong.  Let's work on the error messages,
not keeping the language harder to understand for more general programs.

-- 
Aaron Denney
-><-

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


Re: Re[2]: Class System current status

2006-05-16 Thread Aaron Denney
On 2006-05-15, Bulat Ziganshin <[EMAIL PROTECTED]> wrote:
> Hello Aaron,
>
> Monday, May 15, 2006, 12:27:43 AM, you wrote:
>
>>> IMHO the right thing is to decouple finalising an FD/AT appendix from
>>> finalising the main body of Haskell'.  This is clearly more easily
>>> realised when the delayed material is out-of-line.
>
>> Meh.  I'd really like a revised numeric prelude to be able to use MPTCs
>> with FDs.
>
> other well-known uses of FDs are also in the heart of core Haskell
> libs - collections, monad transformers, streams

Sure, it's just I question how core those are.  The math stuff pretty
much needs to be built in, especially considering things like
defaulting, and syntactic sugar.

-- 
Aaron Denney
-><-

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


Re: Class System current status

2006-05-14 Thread Aaron Denney
On 2006-05-13, Manuel M T Chakravarty <[EMAIL PROTECTED]> wrote:
> Stephanie Weirich:
>> Simon Peyton-Jones wrote:
>> > My suggestion is this:
>> >
>> > * Specify MPTCs in the main language
>> >
>> > * Specify FDs in an Appendix (with some reasonably conservative
>> >interpretation of FDs). 
>> >
>> > * A Haskell' implementation should implement the Appendix, and
>> >programmers can write programs against it.  But
>> >we are advertising specifically that we aren't sure, one way
>> >or the other, whether FDs will stay in the language for ever
>> >
>> >   
>> Simon,
>> 
>> Why is an Appendix is better than just a footnote in the Standard that 
>> says "we aren't sure, one way or the other, whether FDs will stay in the 
>> language for ever."  Why do we need this extra structure?
>
> IMHO the right thing is to decouple finalising an FD/AT appendix from
> finalising the main body of Haskell'.  This is clearly more easily
> realised when the delayed material is out-of-line.

Meh.  I'd really like a revised numeric prelude to be able to use MPTCs
with FDs.

-- 
Aaron Denney
-><-

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


Re: WordPtr,IntPtr,IntMax,WordMax

2006-05-01 Thread Aaron Denney
On 2006-04-29, Manuel M T Chakravarty <[EMAIL PROTECTED]> wrote:
> Am Donnerstag, den 06.04.2006, 16:37 -0700 schrieb John Meacham:
>> On Thu, Apr 06, 2006 at 04:28:01PM -0700, John Meacham wrote:
>> > I was curious if ghc could support the following basic types, they will
>> > likely just be aliases of existing types.
>> > 
>> > WordPtr uintptr_t
>> > WordMax uintmax_t
>> > IntPtr  intptr_t
>> > IntMax  intmax_t
>> > 
>> > all these C types are defined by ISO C so should be available,
>> > otherwise, they are easy enough to generate in ghcs autoconf script.
>> > 
>> > jhc provides these under these names in Data.Word and Data.Int.
>> > they would be useful for writing jhc/ghc portable low level code, and
>> > writing 32/64 bit safe code.
>> 
>> oh, I forgot the all important conversion routines,
>> 
>> ptrToWordPtr :: Ptr a -> WordPtr
>> wordPtrToPtr :: WordPtr -> Ptr a
>> 
>> ptrToIntPtr :: Ptr a -> IntPtr
>> intPtrToPtr :: IntPtr -> Ptr a
>> 
>> jhc makes these available in Jhc.Addr, but if ghc decides to provide
>> them in a common spot (Foreign.Ptr maybe?)
>> 
>> then I will have jhc follow suit.
>> 
>> I'd also propose these be added to the FFI standard.
>
> I collect additions to the FFI on the Haskell' wiki:
>
>   http://hackage.haskell.org/trac/haskell-prime/wiki/ForeignFunctionInterface
>
> I added a note about these types.  Any other ISO C types that we should
> include?

complex .

-- 
Aaron Denney
-><-

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


Re: FFI, safe vs unsafe

2006-04-11 Thread Aaron Denney
On 2006-04-11, Ross Paterson <[EMAIL PROTECTED]> wrote:
> On Tue, Apr 11, 2006 at 09:13:00AM +0100, Simon Marlow wrote:
>>  - the default should be... concurrent reentrant, presumably, because
>>that is the safest.  (so we need to invert the notation).
>
> I think the name "concurrent" has a similar problem to "safe": it reads
> as an instruction to the implementation, rather than a declaration by the
> programmer of the properties of a particular function; as Wolfgang put it,
> "this function might spend a lot of time in foreign lands".

I'd like to second this.

-- 
Aaron Denney
-><-

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


Re: bringing discussions to a close

2006-03-28 Thread Aaron Denney
On 2006-03-29, isaac jones <[EMAIL PROTECTED]> wrote:
> On Tue, 2006-03-28 at 21:16 -0500, Jim Apple wrote:
>> On 3/28/06, isaac jones <[EMAIL PROTECTED]> wrote:
>> > The only topics that should remain open are concurrency and
>> > the class system.
>> 
>> What happene to bullet 3, "perhaps standard libraries"?
>
> We're still trying to figure out exactly what the 3rd topic should be.
> I don't want to hold up discussion on the other topics, though.
> Standard libraries is at the top of my list right now because it has
> hardly been discussed.

A lot of the design decisions for standard libraries do depend on
details of the class system, as well.

-- 
Aaron Denney
-><-

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


Re: Pre-emptive or co-operative concurrency (was: Concurrency)

2006-03-28 Thread Aaron Denney
On 2006-03-28, Malcolm Wallace <[EMAIL PROTECTED]> wrote:
> Another piece of terminology to clear up.  By "non-blocking foreign
> call", you actually mean a foreign call that *can* block.  As a
> consequence of the fairness policy, you wish to place the requirement on
> implementations that such a blocking foreign call _should_not_
> block progress of other Haskell threads.  The thread-nature of the
> foreign call is "blocking".  The Haskell-API nature is desired to be
> "non-blocking".

*glyph of enlightenment*.
Ah, no wonder a lot of the discussion and docs didn't seem to make sense.

-- 
Aaron Denney
-><-

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


Re: Re[2]: important news: refocusing discussion

2006-03-27 Thread Aaron Denney
On 2006-03-28, Taral <[EMAIL PROTECTED]> wrote:
> On 3/27/06, Ross Paterson <[EMAIL PROTECTED]> wrote:
>> How about STM (minus retry/orElse) and TVars as the portable interface?
>> They're trivial for a single-threaded implementation, and provide a
>> comfortable interface for everyone.
>
> +1 on STM as the core interface. Why do you suggest omitting retry/orElse?

-1.  STM is a cool little abstraction making it easy to write dead-lock
free code.  I haven't wrapped my head around writing _quick_ dead-lock free
code, where as the MVar model has all sorts of abstractions built that
make that, well, not _easy_, but the difficulties are understood.

-- 
Aaron Denney
-><-

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


Re: the MPTC Dilemma (please solve)

2006-03-25 Thread Aaron Denney
On 2006-03-21, Manuel M T Chakravarty <[EMAIL PROTECTED]> wrote:
> Aaron Denney:
>> On 2006-03-20, Manuel M T Chakravarty <[EMAIL PROTECTED]> wrote:
>> > IMHO if we consider deprecating a feature in Haskell'' again,
>> > we should not include it in Haskell', but leave it as an optional extra
>> > that some systems may experimentally implement and some may not.
>> 
>> Possibly true, but it still needs to be standardized so that it will
>> work the same on different implementations.
>
> It might be standardised as an add on to the language standard, instead
> of as part of the language standard.

Fair enough, but the time frame for it to be useful implies
standardizing it now, rather than after the rest is standardized.

-- 
Aaron Denney
-><-

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


Re: Ranges and the Enum class

2006-03-20 Thread Aaron Denney
On 2006-03-20, Wolfgang Jeltsch <[EMAIL PROTECTED]> wrote:
> Am Freitag, 17. März 2006 18:49 schrieb Ross Paterson:
>> [...]
>
>> 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.

Which could still be useful.

> It's often not clear 
> how toEnum and fromEnum should look like.  How should they be implemented for 
> Time.Day, for example?  Should the days corresponds to the integers 0 to 6 or 
> 1 to 7?

I believe that 0 to n-1 is the standard representation that deriving Enum 
currently
uses.

>> It seems that succ and pred are unused. 
>
> No, I use them.  In my opinion, it makes much more sense to write succ n than 
> n + 1.

Agreed, for non-arithmetical types.

-- 
Aaron Denney
-><-

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


Re: the MPTC Dilemma (please solve)

2006-03-20 Thread Aaron Denney
On 2006-03-20, Manuel M T Chakravarty <[EMAIL PROTECTED]> wrote:
> IMHO if we consider deprecating a feature in Haskell'' again,
> we should not include it in Haskell', but leave it as an optional extra
> that some systems may experimentally implement and some may not.

Possibly true, but it still needs to be standardized so that it will
work the same on different implementations.

-- 
Aaron Denney
-><-

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


Re: Ranges and the Enum class

2006-03-18 Thread Aaron Denney
On 2006-03-18, Aaron Denney <[EMAIL PROTECTED]> wrote:
> class ArithmeticSequence a where
> stepFrom  :: a -> [a]-- [n..]
> stepFromBy:: a -> a -> [a]   -- [n,n'..]
> stepFromTo:: a -> a -> [a]   -- [n..m]
> stepFromByTo  :: a -> a -> a -> [a]  -- [n,n'..m]

Whoops, it was a big thinko to change "Then" to "By" here.
These should be stepFromThenTo, etc.

-- 
Aaron Denney
-><-

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


Re: Ranges and the Enum class

2006-03-18 Thread Aaron Denney
On 2006-03-18, Jim Apple <[EMAIL PROTECTED]> wrote:
> On 3/18/06, Aaron Denney <[EMAIL PROTECTED]> wrote:
>> Rational _could_ be added here by the diagonal representation, but
>> probably sohuldn't.
>
> We could also add an actual enumeration of rationals, as in
> http://web.comlab.ox.ac.uk/oucl/work/jeremy.gibbons/publications/rationals.pdf
>
> It would be quite confusing to write, say, [1%2 .. 3%2] and get 2%1
> and 1%3 in the middle!

Right, hence my desire to make it a sequence, but not Enumerable, since
it has quite a few different quasi-natural ways of doing so.

-- 
Aaron Denney
-><-

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


Re: Ranges and the Enum class

2006-03-17 Thread Aaron Denney
On 2006-03-17, Ross Paterson wrote:
> Speaking of confusing, try
>
>   [0, 0.3 .. 2]::[Rational]

Right.  I had forgotten that -- Rational is exact, yet has the weird
"closest endpoint" behavior of Float and Double.

> Also, toEnum and fromEnum would make more sense mapping from and to
> Integer.  It seems that succ and pred are unused.

So, I think I'll put together a proposal, well two.
Okay, three.

First, change toEnum and fromEnum to Integer.

Then there is a choice between:
(1): Remove Double, Float, and Rational from Enum.  They're no longer
usable in arithmetic sequences.

Pro: Very easy to do.
 Sequences can still be constructed by starting with
 integers, and scaling to convert.
Con: Loses some functionality (though it's questionable
 functionality given rounding).

(2): Split Enum into the classes Enum and ArithmeticSequence
and change what the various [..] desugars to.

class Enum a where
succ, pred :: a -> a
toEnum :: Integer -> a
fromEnum   :: a -> Integer

I believe succ and pred aren't used directly by anything else, but I do like
having them.

instance Integer, Int

Rational _could_ be added here by the diagonal representation, but
probably sohuldn't.

class ArithmeticSequence a where
stepFrom  :: a -> [a]-- [n..]
stepFromBy:: a -> a -> [a]   -- [n,n'..]
stepFromTo:: a -> a -> [a]   -- [n..m]
stepFromByTo  :: a -> a -> a -> [a]  -- [n,n'..m]

instance Int, Integer, Float, Double, Rational.

(a) Make all of them have the "closest endpoint" behavior.
(b) Make all of them have strict "no more than" behavior.

Pros: Clearly divides two seperate uses, while keeping functionality.
  Can re-introduce relationship between Ix and Enum?
Cons: Yet another typeclass.
  Slightly misleading name, as non-arithmetic structures _should_ be
  supported.  Also a bit long.
  But doing so automatically is tricky, as toEnum and fromEnum are no
  longer accessible
  Keeps questionable functionality of non-exact arithmetic sequences.

Personally, I'm for 2(a), but I think even (1) is an improvement.

It's a pity we can't make Enum a subclass of ArithmeticSequence that
provides the methods of its superclass.  Would it be possible to have
"data ... (deriving ArithmeticSequence)" check if (Num a, Ord a) is
defined and use (+), else if Enum a is defined, use fromEnum/toEnum to
go through Integer, else fail.

Where I suppose defined must mean "defined in this module".  Hmm.  That's
kind of ugly.  I can see why these were combined, but it's still really
ugly.

Steppable might be a better name.

Comments anyone?

-- 
Aaron Denney
-><-

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


Ranges and the Enum class

2006-03-17 Thread Aaron Denney
Sometime back on one of the other Haskell lists, there was a proposal
to not have the floating types instances of Enum and instead have some
other class to which [a, b..c] desugars.  That is, rename enumFromThen
and friends and put them in another class.  Put simply, Float and Double
should not support succ and pred (unless, perhaps, they map to the next
greater/lesser representable number, which would also be confusing).
I can even see an argument for not allowing Float or Double to be used
for ranges either, as the steps may not be exact, which in practice
turns out to be very confusing.

This is a wart I would really like to see get fixed.

-- 
Aaron Denney
-><-

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


Re: Export lists in modules

2006-02-23 Thread Aaron Denney
On 2006-02-21, Wolfgang Jeltsch <[EMAIL PROTECTED]> wrote:
> Am Dienstag, 21. Februar 2006 04:41 schrieb 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
>
> On the other hand, sometimes it makes sense to have a "mostly qualified" 
> import.  For example, if you import Data.Set or Data.Map you might want only 
> the type constructors to be imported unqualified and the rest to be imported 
> qualified.

import qualified Foo

unqualify1 = Foo.unqualify1
unqualify2 = Foo.unqualify2
...

(That is, this is already pretty easy to do.)

-- 
Aaron Denney
-><-

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


Re: pattern guards (was: Parallel list comprehensions)

2006-02-16 Thread Aaron Denney
On 2006-02-16, Claus Reinke <[EMAIL PROTECTED]> wrote:
>> Oh golly. I can't live without pattern guards. they are the best darn
>> thing since sliced bread. I highly recommend them. I .. would have 
>> to seriously refactor a ton of code if pattern guards disapeared.
>> 
>> So much so that it would be less work to implement pattern guards for
>> other compilers and submit the patches.
>
> eh, well, pattern guards are nice. but, many of their uses are also 
> easily replaced, by moving the pg-monad from the lhs to the rhs,
> and employing MonadPlus for the fall-throughs; something roughly 
> like:
>
> f p1 | g1 = e1
> ..
> f pn | gn = en
> where 
>
> -->
>
> f x = fromJust $ do {p1 <- return x; guard g1; return e1}
> ..
> `mplus` do {pn <- return x; guard gn; return en}
>     where 

This works, of course, but it looks far far uglier, and is harder to
type.

-- 
Aaron Denney
-><-

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


Re: FilePath as ADT

2006-02-03 Thread Aaron Denney
On 2006-02-03, Ross Paterson <[EMAIL PROTECTED]> wrote:
> On Fri, Feb 03, 2006 at 12:24:28PM +, Axel Simon wrote:
>> Yes, and I suppose not being opaque about a file name (i.e. FilePath =
>> [Word8]) is superior.
>
> Maybe.  You might want [Word8] under Unix and [Word16] under Win32.

Right.  I think "Generic File Handling" should not be considered the
base, but layered on top of Unix, Win32 and possibly MacOS, if unix
doesn't cover that.

-- 
Aaron Denney
-><-

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


Re: Priorities

2006-02-03 Thread Aaron Denney
On 2006-02-03, John Goerzen <[EMAIL PROTECTED]> wrote:
> On Fri, Feb 03, 2006 at 05:56:41PM +0100, Tomasz Zielonka wrote:
>> On Fri, Feb 03, 2006 at 10:03:08AM -0600, John Goerzen wrote:
>> > I know, of course, that Java green threads and Haskell forkIO threads
>> > are called "threads", but I personally believe its misleading to call it
>> > concurrency -- they're not doing more than one thing at a time.
>> 
>> Aren't you thinking about Parallellism?
>
> No.
>
>> http://en.wikipedia.org/wiki/Concurrency_%28computer_science%29
>> In computer science, concurrency is a property of systems which
>> consist of computations that execute overlapped in time
>
> You're not doing anything simultaneously ("overlapped in time") when
> you're using poll and select (only).  To do something simultaneously in
> Unix, you'd have to either use fork() or start a thread.

That was his point.  Threading is a way of structuring a program.
Parallelism is a strategy for exploiting that structuring (and others).

-- 
Aaron Denney
-><-

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


Re: separate class and type namespace

2006-01-31 Thread Aaron Denney
On 2006-01-31, Johannes Waldmann <[EMAIL PROTECTED]> wrote:
>
>> Marcin 'Qrczak' Kowalczyk <[EMAIL PROTECTED]> writes:
>>> Type signatures too should be allowed in export lists.
>
> I'm all for type signatures, but I am slightly worried in that this
> leads to duplication of information (giving the signature both in the
> export list and at the place of definition). What about having
> "private/public" access modifiers at the points of definition instead,
> and removing export lists altogether?

Reexporting from sub-modules.

-- 
Aaron Denney
-><-

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


Re: Removal candidates in patterns

2006-01-26 Thread Aaron Denney
On 2006-01-26, Olaf Chitil <[EMAIL PROTECTED]> wrote:
>
> I am very please to see on the Wiki also a list of removal candidates 
> and that these include n+k patterns and ~ patterns.
>
> I'd like to add one pattern to this list of removal candiates: k 
> patterns, that is, numeric literals.

I don't see that much use for the first two but I really want to
argue for being able to pattern-match on numeric literals.  I think
numeric literals should be treated as much as possible as if there were
declarations like "data Int = 0 | 1 | (-1) | 2 | (-2) | ..."

Or am I misunderstanding the suggestion here?

> Iff n+k patterns are removed, there is little good use for k patterns 
> either.

Say what?  n+k could perhaps serve some pedagogical purpose in
presenting the peano numbers.  Plain old literals are not so tied to
a particular representation (that is, you can imagine 4 being expanded
to match Int# 4, or BooleanSequence [T,F,F] internally, or whatever and
still looking exactly the same in the code), and have the same utility
as being able to pattern-match any data.

> So get rid of these three and pattern matching becomes so much more simple.

>From the point of view of Hat, yes.  Despite how useful hat is, I'd
rather have the ability to do 

ack 0 n = n+1
ack m 0 = ack (m-1) 1
ack m n = ack (m-1) (ack m (n-1))

which looks far nicer than

ack m n | m == 0 = n + 1
| n == 0 = ack (m-1) 1
| otherwise = ack (m-1) (ack m (n-1))

I admit this is 99% aesthetics, but aesthetics do matter, as does
consistency and regularity.  And there are some cases where the guards
can get quite complex, especially when rewriting something that already
combines pattern-matching with guards.

-- 
Aaron Denney
-><-

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


Re: The dreaded M-R

2006-01-26 Thread Aaron Denney
On 2006-01-26, John Hughes <[EMAIL PROTECTED]> wrote:
> I don't think it's hard. I would just teach students to define
> functions with =, and "variables" with :=. I tell my students to write
> type signatures at the beginning anyway, so they don't risk being
> bitten by the M-R anyway. Beginning students just do what you tell
> them, and they already think of function and variable definitions as
> different. Learning a different syntax for one of them would not be a
> problem.
>
> Once they've mastered basic programming and start getting interested
> in things like overloading, then you have to explain how the M-R
> works. I'd much rather explain =/:= than try to teach them how you
> know whether a definition is shared or not right now.

And this gets back to "what the target audience for Haskell' is"
question.  Since I'm not a CS student, and I'm not teaching CS students,
this whole argument is rather unconvincing to me.

-- 
Aaron Denney
-><-

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


Re: more flexible partial application

2006-01-26 Thread Aaron Denney
On 2006-01-26, Dinko Tenev <[EMAIL PROTECTED]> wrote:
> On 1/26/06, Conor McBride <[EMAIL PROTECTED]> wrote:
> [...]
>> We'd do daft stuff like
>>
>>   (200 * _ ^ 2) unitsquare
>
> Yes, I played with a concept like that at one point, and came to the
> conclusion that it was better done with lambdas.  I am all
> specifically about function application, not arbitrary expressions.

Arbitrary expressions are just function application.

>> If you do want to pull a stunt like this, you need some other funny
>> brackets which specifically indicate this binding power, and then you
>> can do grouping inside them, to create larger linear abstractions. You
>> could have something like
>>
>>   (| f (_ * 3) _ |)
>
> We already have lambdas for this, and they're shorter, clearer, and
> more powerful.

The same hold (except for shorter) for this whole extension, and I don't
know that "shorter" holds here.

-- 
Aaron Denney
-><-

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


OT: Re: more flexible partial application

2006-01-25 Thread Aaron Denney
On 2006-01-25, Dinko Tenev wrote:
> a huge base64 blob.

Which, sadly, makes it harder for me to read your messages.

I don't suppose there's anyway to get gmail to only label messages as
UTF-8 only if they contain non-ascii?

-- 
Aaron Denney
-><-

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


Numeric class lattice reworking?

2006-01-23 Thread Aaron Denney
One of the complaints I've seen with people trying to do various
mathematical tasks in haskell is the inflexibility of the numeric
prelude.  The biggest issue is having (*) and (+) in the same
typeclass, but other generalizations are certainly possible.
MPTC would allow such things as modules with (*) having type a -> b -> b
which covers everything from group actions to scalar multiplication
of vectors.

Actually, a -> b -> c would be nice.  See
http://haskell.org/hawiki/DimensionalizedNumbers 
this would let me have multiplication of numbers with units, enforced at
the type level, while keeping the safety of (+) :: a -> a -> a.

Is there any chance of this sort of breakup happening?

-- 
Aaron Denney
-><-
___
Haskell-prime mailing list
[EMAIL PROTECTED]
http://haskell.org/mailman/listinfo/haskell-prime