Re: map and fmap

2006-08-30 Thread Jon Fairbairn

I don't really have the stamina to keep up with discussions
like this. I have a bit more now than the first time round,
so here's some more...

On 2006-08-29 at 07:58+0200 John Hughes wrote:

 On the contrary, it seems we had plenty of experience with an overloaded 
 map--it was in the language for two and a half years,

During which there were fewer users, as you note below.

 and two language versions. In the light of that
 experience, the Haskell 98 committee evidently decided
 that overloading map was a mistake, and introduced fmap
 for the overloaded version.

One might say that your experience persuaded the committee
to do this.

 Now, this was an incompatible change, and the Haskell
 committee was always very wary of making such changes--so
 there must have been a weight of experience suggesting
 that overloading map really was a mistake.

For teaching, yes.

 It wouldn't have been changed on the basis of abstract
 discussions of small examples. My own bad experiences with
 list overloading were with monad comprehensions, but
 others must have had bad experiences with overloaded map
 also. Given that it's been tried--and tried so
 thoroughly--and then abandoned, I would be very wary of
 reintroducing it.

I don't think you can conclude that from the evidence
available (ie the link, posted by Ross Paterson, to the
discussion at the time)

 We didn't simplify things in Haskell 98 for the sake of
 it--we simplified things because users were complaining
 that actually using the language had become too complex,
 that there were too many corners to stumble on.


This is where I most heartily disagree. Whatever the
arguments for and against, what was done was /not/ a
simplification of the language.

I cannot see how it can be argued that a language where

* the functorial map has three names (fmap, liftM and map)
  at different types

* and the general functorial map (fmap) can be applied only
  to some Monads (the ones where an instance has explicitly
  given)

is simpler than a language where

* the functorial map is called map.

Your argument that teaching the former language is simpler
is very strong and I don't dispute it, but it is not, I
think, a reason to require that people who want to use the
language to have to put up with remembering extra
complexity.  Once one knows what functors and monads are
(and no one can call themselves an expert Haskell programmer
who does not), one should not have to think does this Monad
have an instance of Functor, or must I use liftM? or is
this function /really/ meant to work only on lists, or can I
replace map with fmap and get it to work on something else
(and then find that it requires copying out the whole
definition because it also uses ++ or something).

Yes, it makes perfect sense to have

 mapList = (map :: (a-b) - [a] - [b])

in a prelude somewhere for teaching purposes, but aren't
people eventually taught that mapList is just a specialised
version of map, ++ is `mplus` specialised to lists (etc),
and that one should think in terms of defining operations
that are as generally useful as possible?

At which point don't some of them start to wish that they
could just type ++ instead of mplus? I certainly do. If it
were just a question of map and fmap, I might agree that the
cost would outweigh the benefit, but there's a whole swathe
of functions for which I'd rather see the nicer names used
for the more general versions, and clumsier ones for the
versions specialised to lists for teaching purposes.

We would all benefit from better error messages, but that's
a different problem.

 I think we did a good job--certainly, the Haskell
 community began growing considerably faster once Haskell
 98 came out.

I'm not sure there's a causal relationship there. If the
growth was anything above linear, it would be growing faster
later whether or not Haskell 98 had an effect. Even if
Haskell 98 was the cause, it's far from obvious that this
particular change was the one that made the
difference... and if it did, it may not have done so for a
good reason.  If you make the language easier to understand
it may well become more popular (there are plenty of awfully
popular awful languages out there for more or less that
reason), but if it's at the expense of unnecessarily complex
programmes, we shouldn't be applauding ourselves too much.

In addition, it seems likely that as more and more people
get a deeper understanding of Functors, Applicators and
Monads, we'll find better ways of teaching them.

 Jón


-- 
Jón Fairbairn  Jon.Fairbairn at cl.cam.ac.uk


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


Re: map and fmap

2006-08-30 Thread Cale Gibbard

I haven't really been able to follow this entire thread, but I'd just
like to note here that I agree completely with Jón's take here on the
map issue. It's almost embarassing to have to tell people that there
are 3 functions in the basic libraries which do exactly the same thing
up to type signature. The issue with choosing fmap or liftM is even
worse. I usually go with fmap because it's in the Prelude and seems
more general anyway, but then, some monads aren't in Functor so I need
to be careful about creating class contexts with both Monad and
Functor constraints. Please, let's fix this. Nice general interfaces
are good. While we're at it, let's split MonadZero and MonadPlus --
the decision to merge them was not well thought-out, and a lot of
expressive power in type signatures is lost there.

I'm not sure I agree with Jón's earlier sentiment with regards to
taking everything out of the Prelude and requiring the user to import
many separate modules though. :) While the idea of producing as clean
a language as possible is attractive, the most commonly used list,
monad, and IO functionality is pretty nice to have available without
extra imports. It would also be nice to have all the usual instances
handy straight away.

In any case, it's probably a good idea to at least have those things
in separate modules, and then possibly reexported by the Prelude, as
far as structuring things goes.

I think it would be reasonable to expect the Prelude to include enough
things to provide for basic idiomatic Haskell programming, as it
(mostly) does currently. I already tend to import Data.List and
Control.Monad preemptively, but I should probably be more careful and
take note of which things I should be nagging people to move upward.
At the very least, join should be a member of the Monad class, so it
ought to be there. :)

Lists essentially take the place of loops in Haskell, and even in C,
you don't need to do an #include to get 'for'. I think the issue is
basically one of striking a balance between cleanliness of design, and
ability to write quick (1 to 10 line) programs conveniently.

Over time, the standard practice of writing Haskell code changes too.
For example things like the monad instance for ((-) e) (that is, the
lightweight reader monad) are becoming more popular -- to the point
where I'd mostly feel comfortable asking to have that put in the
Prelude. (All the people who hang around in #haskell have likely
picked up a few idioms from the @pl lambdabot module though -- perhaps
we're a biased sample ;)

- Cale

On 30/08/06, Jon Fairbairn [EMAIL PROTECTED] wrote:


I don't really have the stamina to keep up with discussions
like this. I have a bit more now than the first time round,
so here's some more...

On 2006-08-29 at 07:58+0200 John Hughes wrote:

 On the contrary, it seems we had plenty of experience with an overloaded
 map--it was in the language for two and a half years,

During which there were fewer users, as you note below.

 and two language versions. In the light of that
 experience, the Haskell 98 committee evidently decided
 that overloading map was a mistake, and introduced fmap
 for the overloaded version.

One might say that your experience persuaded the committee
to do this.

 Now, this was an incompatible change, and the Haskell
 committee was always very wary of making such changes--so
 there must have been a weight of experience suggesting
 that overloading map really was a mistake.

For teaching, yes.

 It wouldn't have been changed on the basis of abstract
 discussions of small examples. My own bad experiences with
 list overloading were with monad comprehensions, but
 others must have had bad experiences with overloaded map
 also. Given that it's been tried--and tried so
 thoroughly--and then abandoned, I would be very wary of
 reintroducing it.

I don't think you can conclude that from the evidence
available (ie the link, posted by Ross Paterson, to the
discussion at the time)

 We didn't simplify things in Haskell 98 for the sake of
 it--we simplified things because users were complaining
 that actually using the language had become too complex,
 that there were too many corners to stumble on.


This is where I most heartily disagree. Whatever the
arguments for and against, what was done was /not/ a
simplification of the language.

I cannot see how it can be argued that a language where

* the functorial map has three names (fmap, liftM and map)
  at different types

* and the general functorial map (fmap) can be applied only
  to some Monads (the ones where an instance has explicitly
  given)

is simpler than a language where

* the functorial map is called map.

Your argument that teaching the former language is simpler
is very strong and I don't dispute it, but it is not, I
think, a reason to require that people who want to use the
language to have to put up with remembering extra
complexity.  Once one knows what functors and monads are
(and no one can call themselves an expert

Re: map and fmap

2006-08-30 Thread Ashley Yakeley

Cale Gibbard wrote:

While we're at it, let's split MonadZero and MonadPlus --
the decision to merge them was not well thought-out, and a lot of
expressive power in type signatures is lost there.


This should be split into three classes, MonadZero, MonadPlus and 
MonadOr owing to variations in instances of the current MonadPlus.


See:
  http://haskell.org/haskellwiki/MonadPlus
  http://haskell.org/haskellwiki/MonadPlus_reform_proposal

--
Ashley Yakeley
Seattle WA

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


Re: map and fmap

2006-08-30 Thread Cale Gibbard

Indeed, I agree.

On 30/08/06, Ashley Yakeley [EMAIL PROTECTED] wrote:

Cale Gibbard wrote:
 While we're at it, let's split MonadZero and MonadPlus --
 the decision to merge them was not well thought-out, and a lot of
 expressive power in type signatures is lost there.

This should be split into three classes, MonadZero, MonadPlus and
MonadOr owing to variations in instances of the current MonadPlus.

See:
   http://haskell.org/haskellwiki/MonadPlus
   http://haskell.org/haskellwiki/MonadPlus_reform_proposal

--
Ashley Yakeley
Seattle WA

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


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


Re: map and fmap

2006-08-29 Thread John Hughes




On 8/28/06, John Hughes [EMAIL PROTECTED] wrote:

No, map was never overloaded--it was list comprehensions that were
overloaded as monad comprehensions in Haskell 1.4. That certainly did 
lead

to problems of exactly the sort John M is describing.


I just checked the reports for Haskell 1.3 and 1.4 on the Haskell
website and they both state that the method of 'Functor' was 'map'.  I
only started using Haskell towards the end of 1.4, so I don't have
much experience with those versions of the language, but it seems that
having an overloaded 'map' was not much of a problem if only a few
people noticed.

-Iavor



Good Lord, I'd forgotten that! So I'm afraid I've also forgotten the details 
of the arguments that led to fmap being introduced--maybe others can fill 
them in. But I wouldn't conclude from that that only a few people noticed 
and so it would be OK to overload map again.


On the contrary, it seems we had plenty of experience with an overloaded 
map--it was in the language for two and a half years, and two language 
versions. In the light of that experience, the Haskell 98 committee 
evidently decided that overloading map was a mistake, and introduced fmap 
for the overloaded version. Now, this was an incompatible change, and the 
Haskell committee was always very wary of making such changes--so there must 
have been a weight of experience suggesting that overloading map really was 
a mistake. It wouldn't have been changed on the basis of abstract 
discussions of small examples. My own bad experiences with list overloading 
were with monad comprehensions, but others must have had bad experiences 
with overloaded map also. Given that it's been tried--and tried so 
thoroughly--and then abandoned, I would be very wary of reintroducing it.


We didn't simplify things in Haskell 98 for the sake of it--we simplified 
things because users were complaining that actually using the language had 
become too complex, that there were too many corners to stumble on. I think 
we did a good job--certainly, the Haskell community began growing 
considerably faster once Haskell 98 came out. So I'd be very nervous about 
undoing some of the simplifications we made at that time.


John



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


Re: map and fmap

2006-08-29 Thread Ross Paterson
On Tue, Aug 29, 2006 at 07:58:58AM +0200, John Hughes wrote:
 [Iavor wrote:]
 I just checked the reports for Haskell 1.3 and 1.4 on the Haskell
 website and they both state that the method of 'Functor' was 'map'.
 
 Good Lord, I'd forgotten that! So I'm afraid I've also forgotten the 
 details of the arguments that led to fmap being introduced--maybe others 
 can fill them in.

http://www.cs.chalmers.se/~rjmh/Haskell/Messages/Decision.cgi?id=362

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


Re: map and fmap

2006-08-28 Thread Taral

On 8/28/06, John Hughes [EMAIL PROTECTED] wrote:

As for an example of fmap causing trouble, recall the code I posted last
week sometime:

class Foldable f where
  fold :: (a - a - a) - a - f a - a


I'd call this a case of Foldable causing trouble. :) Fold is
somewhat specific to the structure of the underlying collection (hence
the numerous fold* functions), map is not.

--
Taral [EMAIL PROTECTED]
You can't prove anything.
   -- Gödel's Incompetence Theorem
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


Re: map and fmap

2006-08-28 Thread Iavor Diatchki

Hello,

On 8/28/06, John Hughes [EMAIL PROTECTED] wrote:

No, map was never overloaded--it was list comprehensions that were
overloaded as monad comprehensions in Haskell 1.4. That certainly did lead
to problems of exactly the sort John M is describing.


I just checked the reports for Haskell 1.3 and 1.4 on the Haskell
website and they both state that the method of 'Functor' was 'map'.  I
only started using Haskell towards the end of 1.4, so I don't have
much experience with those versions of the language, but it seems that
having an overloaded 'map' was not much of a problem if only a few
people noticed.



As for an example of fmap causing trouble, recall the code I posted last
week sometime:

class Foldable f where
  fold :: (a - a - a) - a - f a - a

instance Foldable [] where
  fold = foldr

example = fold (+) 0 (fmap (+1) (return 2))

Here nothing fixes the type to be lists. When I posted this, someone called
it contrived because I wrote return 2 rather than [2], which would have
fixed the type of fmap to work over lists. But I don't think this is
contrived, except perhaps that I reused return from the Monad class, rather
than defining a new collection class with overloaded methods for both
creating a singleton collection and folding an operator over a collection.
This is a natural thing to do, in my opinion, and it leads directly to this
example.


I don't think this example illustrates a problem with 'fmap'.  The
problem here is that we are using both an overloaded constructor
(return) and destructor (fold), and so nothing specifies the
intermediate representation.   The fact that 'map' removed the
ambiguity was really an accident. What if we did not need to apply a
function to all elements?

example = fold (+) 0 (return 2)

It seems that we could use the same argument to reason  the 'return'
should have the type 'a - [a]', or that we should not overload
'fold', which with the above type seems to be fairly list specific.

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


Re: map and fmap

2006-08-23 Thread Iavor Diatchki

Hello,

On 8/22/06, John Meacham [EMAIL PROTECTED] wrote:

I am not talking about type signatures, I am talking about having to
annotate in the middle of a term.

f x y | x `member` map g freeVars y  = 

having to become

f x y | x `member` map g (freeVars y :: [Id])  = 


There is no need to write such types... In this particular case the
type of 'elem' indicates that the argument is a list.  I don't think
that a polymorphic 'map' function requires any more signatures than,
say, '='.  This certainly is not my experience when I use 'fmap'...


So, I am not saying renaming fmap to map is bad outright, I am just
saying that the question is trickier than just the error message problem
it was previously stated in terms of.


Do you have an example illustrating what is tricky about 'fmap'?  As
far as I understand 'map' used to be polymorphic, and later the
distinction between 'map' and 'fmap' was specifically introduced to
avoid the error messages that may confuse beginners.

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


Re: map and fmap

2006-08-22 Thread Iavor Diatchki

Hello,
I agree that this is a small change, and I don't expect that it will happen.

On 8/21/06, John Meacham [EMAIL PROTECTED] wrote:

Yeah, the change doesn't seem worth it to me. And I still have concerns
about ambiguity errors, if a beginner ever has to use an explicit type
signature it sort of ruins the whole type inference benefit.


There is a big difference between having to declare all types vs.
writing type signatures only in some places.

In any case, it seems to me that it is good to encourage beginners to
write type signatures, because
(i) it clears their thinking about what they are trying to do,
(ii) it leads to more accurate type errors, because the system can
detect if it is the definition of a function that is wrong or its use.
In fact, I write type signatures for the same reasons.



I think
everyone has tried to write

class Cast a b where
cast :: a - b

at some point but found it not very useful as whenever it was fed or
used as an argument to another overloaded function, you ended up with
ambiguity errors.

with all the added generality being added all over the place, you need
collections of functions that work on concrete data types to 'fix'
things every now and again. lists are common enough that I think they
deserve such 'fixing' functions. And it has nothing to do with newbies.

having to write type annotations when not even doing anything tricky is
not an acceptable solution for a type infered language.


The problem you are describing above is entirely different...
I agree that we should not overload everything, after all there must
be some concrete types in the program.

However, having a 'map' function that is specialized to lists in the
standard library seems quite ad-hoc to me, in a way it is comparable
to saying that 'return' should be specialized to IO, and we should
have 'mreturn' in the Monad class (I am not suggesting this! :-)

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


Re: map and fmap

2006-08-21 Thread Jon Fairbairn
On 2006-08-20 at 15:52+0200 John Hughes 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.

The horror! Yet the code would still work in a sense,
because map is effectively fmap with a type signature
'(fmap::(a-b)-[a]-[b])'. Clearly the programmer meant to
write either 

 example = fold (+) 0 (fmap (+1) [2])

or something with a type signature to disambiguate the
internal overloading -- so I think it's probably a good
thing that this ends up producing an error message, since it
should have been given one in the first place! ;-)

 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.

Certainly (we all want the best error messages possible),
except that we only need to worry about backwards
compatibility for programmes that used to compile. Are there
examples where replacing map with fmap changes the meaning
of the programme?

  Jón


-- 
Jón Fairbairn  Jon.Fairbairn at cl.cam.ac.uk


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


Re: map and fmap

2006-08-21 Thread John Meacham
On Fri, Aug 18, 2006 at 05:30:53PM +0200, John Hughes wrote:
 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.

Yeah, the change doesn't seem worth it to me. And I still have concerns
about ambiguity errors, if a beginner ever has to use an explicit type
signature it sort of ruins the whole type inference benefit. I think
everyone has tried to write 

class Cast a b where
cast :: a - b

at some point but found it not very useful as whenever it was fed or
used as an argument to another overloaded function, you ended up with
ambiguity errors.

with all the added generality being added all over the place, you need
collections of functions that work on concrete data types to 'fix'
things every now and again. lists are common enough that I think they
deserve such 'fixing' functions. And it has nothing to do with newbies.

having to write type annotations when not even doing anything tricky is
not an acceptable solution for a type infered language.

John

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


Re: map and fmap

2006-08-20 Thread John Hughes


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.


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.


John



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


Re: map and fmap

2006-08-20 Thread John Hughes


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.


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.


John



___
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-20 Thread Jeffrey Yasskin

On 8/20/06, 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.


There's a proposal
http://hackage.haskell.org/trac/haskell-prime/wiki/Defaulting that
mentions extending defaulting to other typeclasses. That seems to fix
this particular problem, but above you mentioned that this was a
whole new can of worms. Could you elaborate or point me to a
discussion of the worms?

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


Re: map and fmap

2006-08-17 Thread Jon Fairbairn
On 2006-08-15 at 12:38+0200 John Hughes wrote:
 From: Robert Dockins [EMAIL PROTECTED]
  
 
 On Aug 14, 2006, at 3:00 PM, Iavor Diatchki wrote:
  and I think, that a better approach to problems like these would be to
  have a simplified learning Prelude for the beginners class, rather
  than changing the standard libraries of the language (writing type
  signatures probably also helps...)
 
 This idea has been kicked around a few times, but, AFAIK, it's never
 really been fleshed out. Has anyone ever put anything concrete on
 the table? It seems to me that most complaints are about hard-to-
 understand error messages, and these almost always arise from
 typeclasses. They are especially confusing when they arise from
 syntax sugar. I suppose a prelude with no typeclasses and compiler
 options to make all syntax non-overloaded would be one way to start.
 On a related note, I've seen a number of Haskell design decisions
 justified by the beginners find it difficult argument. Is this
 argument really valid? Is there any reason not to just tell
 beginners to use Helium? Is there a case for something between
 Helium and full H98 (or H')? 
 
 I have a lot of experience of teaching beginners--I've
 been doing it for years,

I'm sure your observations are correct, and it makes a
convincing argument, but I don't buy it completely.

 [...]
 Now, this approach couldn't work if the language I taught
 really WAS only suitable for toy programs!

Granted.

 Even a beginner's prelude would introduce a
 discontinuity for students, making it harder to take the
 step from course exercises to real programs, and that
 would mean that fewer of my students would end up as
 Haskell enthusiasts. I'd be very sad about that.

That would be something to be sad about if true, but it
doesn't convince me that there is no solution. 

Here's what I would like to see:

• Pare the standard prelude down to the bare minimum
  necessary to give types to the basic syntax of the
  language. So 

  ‣ no Int or Double, just Integer and Ratio Integer, so
that constants can be explained. 

  ‣ Given that I'm accepting most of your argument, we'd
have to have List rather than giving [|] and friends
overloaded types -- I don't like that, but I can live
with it.

  ‣ no operations on anything. (Are there any that
absolutely have to be in the prelude?)

• Move all the operations on Lists into List, all arithmetic
  into Integer, Int, Double, Float (or rather
  Arithmetic.Integer etc, and possibly have Arithmetic too
  -- being able to import a bundle of libraries at one go
  seems sensible). Similarly IO and so on.

Now a typical Haskell programme would begin with with a
whole bunch of import statements -- but then all but toy
programmes do anyway, and using the same style doesn't seem
to have caused C any problems.

The beginners' prelude would then consist of several
modules that provided classless versions of the troublesome
overloaded functions, each to be replaced by the real thing
when the source of the trouble had finally been taught. So
what I'm proposing doesn't avoid your objection about a
discontinuity -- in fact it introduces more, but my hope
would be that several small discontinuities rather than one
big one would be sufficiently little trouble. I'll grant
that this is the telling lies to children approach to
teaching, but teaching people Newtonian mechanics before
Einsteinian is generally what happens, and the advantage is
that where it applies it works almost as well as Einstein's
version, and is practical. The same would be true of the
beginners' prelude: folk who only got as far as doing
arithmetic on Integers and Rationals with some simple stuff
on Lists could go on using the simplest beginners' prelude
indefinitely.

True, you'd have to tell your students early on that they
had to put some mumbo-jumbo (import Foo) at the beginning of
their first programmes, but way back in the mists of time I
was taught to programme in some language or other with just
such an incantation, and I'm sure it caused no
problems. Most students are quite happy to follow some
instructions blindly at first (and the ones who aren't are
usually capable of quickly understanding what the
mumbo-jumbo does).


-- 
Jón Fairbairn  Jon.Fairbairn at cl.cam.ac.uk


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


Re[2]: map and fmap

2006-08-15 Thread Bulat Ziganshin
Hello Duncan,

Tuesday, August 15, 2006, 2:37:50 AM, you wrote:

 If it goes in that direction it'd be nice to consider the issue of
 structures which cannot support a polymorphic map. Of course such
 specialised containers (eg unboxed arrays or strings) are not functors
 but they are still useful containers with a sensible notion of map.

unboxed arrays - not if you using implementation from ArrayRef lib

ByteStrings - can be also parameterized by its type elements, as i
always suggested. of course, these elements should be unboxable and
belong to the Storable class in order to allow peek/poke them

there is also faking solution:

type ByteStr a = ByteString
instance Functor ByteStr

(although i never tested it)


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


map and fmap

2006-08-14 Thread Iavor Diatchki

Hello,
I never liked the decision to rename 'map' to 'fmap', because it
introduces two different names for the same thing (and I find the name
`fmap' awkward).

As far as I understand, this was done to make it easier to learn
Haskell, by turning errors like Cannot discharge constraint 'Functor
X' into X =/= List.  I am not convinced that this motivation is
justified, although I admit that I have very limited experience with
teaching functional programming to complete beginners.  Still,
students probably run into similar problems with overloaded literals,
and I think, that a better approach to problems like these would be to
have a simplified learning Prelude for the beginners class, rather
than changing the standard libraries of the language (writing type
signatures probably also helps...)

Renaming 'fmap' to 'map' directly would probably break quite a bit of
code, as all instances would have to change (although it worked when
it was done the other way around, but there probably were fewer
Haskell programs then?).  We could work around this by slowly phasing
out 'fmap': for some time we could have both 'map' and 'fmap' to the
'Functor' class, with default definitions in terms of each other.  A
comment in the documentation would say that 'fmap' is deprecated.  At
some point, we could move 'fmap' out of the functor class, and even
later we could completely remove it.

This is not a big deal, but I thought I'd mention it, if we are
considering small changes to the standard libraries.

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


Re: map and fmap

2006-08-14 Thread Robert Dockins


On Aug 14, 2006, at 3:00 PM, Iavor Diatchki wrote:


Hello,
I never liked the decision to rename 'map' to 'fmap', because it
introduces two different names for the same thing (and I find the name
`fmap' awkward).

As far as I understand, this was done to make it easier to learn
Haskell, by turning errors like Cannot discharge constraint 'Functor
X' into X =/= List.  I am not convinced that this motivation is
justified, although I admit that I have very limited experience with
teaching functional programming to complete beginners.  Still,
students probably run into similar problems with overloaded literals,
and I think, that a better approach to problems like these would be to
have a simplified learning Prelude for the beginners class, rather
than changing the standard libraries of the language (writing type
signatures probably also helps...)


This idea has been kicked around a few times, but, AFAIK, it's never  
really been fleshed out.  Has anyone ever put anything concrete on  
the table?  It seems to me that most complaints are about hard-to- 
understand error messages, and these almost always arise from  
typeclasses.  They are especially confusing when they arise from  
syntax sugar.  I suppose a prelude with no typeclasses and compiler  
options to make all syntax non-overloaded would be one way to start.


On a related note, I've seen a number of Haskell design decisions  
justified by the beginners find it difficult argument.  Is this  
argument really valid?  Is there any reason not to just tell  
beginners to use Helium?  Is there a case for something between  
Helium and full H98 (or H')?




Renaming 'fmap' to 'map' directly would probably break quite a bit of
code, as all instances would have to change (although it worked when
it was done the other way around, but there probably were fewer
Haskell programs then?).  We could work around this by slowly phasing
out 'fmap': for some time we could have both 'map' and 'fmap' to the
'Functor' class, with default definitions in terms of each other.  A
comment in the documentation would say that 'fmap' is deprecated.  At
some point, we could move 'fmap' out of the functor class, and even
later we could completely remove it.

This is not a big deal, but I thought I'd mention it, if we are
considering small changes to the standard libraries.

-Iavor



Rob Dockins

Speak softly and drive a Sherman tank.
Laugh hard; it's a long way to the bank.
  -- TMBG



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


Re: map and fmap

2006-08-14 Thread Duncan Coutts
On Mon, 2006-08-14 at 20:55 +0100, Jon Fairbairn wrote:
 On 2006-08-14 at 12:00PDT Iavor Diatchki wrote:
  Hello,
  I never liked the decision to rename 'map' to 'fmap', because it
  introduces two different names for the same thing (and I find the name
  `fmap' awkward).
 
 I strongly concur. There are far too many maps even without
 that, and having two names for the same thing adds to the
 confusion.

If it goes in that direction it'd be nice to consider the issue of
structures which cannot support a polymorphic map. Of course such
specialised containers (eg unboxed arrays or strings) are not functors
but they are still useful containers with a sensible notion of map.

The proposals to allow this involve MPTCs where the element type is a
parameter. That allows instances which are polymorphic in the element
type or instances which constrain it.

Duncan

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