Re: Standard Haskell

1997-08-20 Thread Jon . Fairbairn

On 20 Aug, Hans Aberg wrote:
>   Is it not possible to make the versions upwards compatible, so that
> Haskell 1.4 code somehow can be run on Haskell 1.5? Does "being stable"
> need to mean unchangeable?

Well, one way would be to require a directive at the head of every file
saying (for example)

Haskell 1.4

And then compilers could always say "Not interested in compiling
Haskell 1.4 programmes"...

I don't think I like this though: it's an extra feature, and the whole
point of the standardisation effort is to replace features by
orthogonality (I hope).

  Jon

-- 
Jon Fairbairn [EMAIL PROTECTED]
18 Kimberley Road[EMAIL PROTECTED]
Cambridge CB4 1HH  +44 1223 570179 (pm only, please)








Re: length that yields Integer - Int is a WART

1997-08-25 Thread Jon . Fairbairn

On 25 Aug, Stephan Tobies wrote:
> I need the length of a list and it should be of type Integer, while the
> prelude function yields type Int.

This looks like a bug in the prelude to me.  It's not inconceivable
that in some implementation it might be possible to have a list with
length greater than the capacity of Int.  So length in the prelude
ought to be Integral a => ...

In general, I think that Int is given too great a prominence -
wherever it is used one is gaining efficiency at the risk of losing
correctness, which is something of which the programmer ought to be
properly aware when coding.

  Jon

-- 
Jon Fairbairn [EMAIL PROTECTED]









List administration question

1997-08-25 Thread Jon . Fairbairn

A cursory examination of the pointers to this list in
http://haskell.org/mailinglist.html> fails to reveal who is
maintaining it, so apologies for sending this to the whole list.

Would it be possible for the list re-mailer to set the 'Reply-to:'
field to point to the list?  Further apologies if this has been
discussed and rejected already.

  Jon

-- 
Jon Fairbairn [EMAIL PROTECTED]







Re: length that yields Integer - Int is a WART

1997-08-25 Thread Jon . Fairbairn

On 25 Aug, Lennart Augustsson wrote:
> That was indeed the original type of length, but it was changed
> for efficiency reasons.  If you want the more general type use
> the genericLength (et al) from the List module.

My belief is that this is a mistake - it's the wrong way round - the
standard prelude ought to have the 'proper' version. The proof would
seem to be that either the compiler can detect that it's safe to use
Int in most cases, in which case we could use the 'proper' version in
the standard prelude, or it's hard to show that it's safe, in which
case the programmer ought to have to think before using the Int
version.


> PS.  Hi Jon!

Hej Lennart!

-- 
Jon Fairbairn [EMAIL PROTECTED]
18 Kimberley Road[EMAIL PROTECTED]
Cambridge CB4 1HH  +44 1223 570179 (pm only, please)









RE: Heap Sort

1997-10-04 Thread Jon . Fairbairn

On  2 Oct , Carsten Kehler Holst wrote:
> Merge Sort vs. Heap Sort (ala Jon)

> As far as I can see the difference between merge sort and heap sort as
> described by Jon is almost non existing.

I'm afraid you need to look a little harder :-)

At first let me note that heapsort as I sent it is flawed in that it
does _more_ comparisons than mergesort for small odd numbers of
elements, so they are not the same!

> mergesort = treefold merge . map runify

you mean treefold merge Nil . map runify

> The main difference is that we call merge recursively instead of
> building a heap node which is later taken apart in flatten_heap.

but the heaps defer some of the comparisons, and group them together
differently.

> I fail to see how Jon's version can be superior and I cannot see
> that points a, b, and c (below) holds (of course (a) can be argued)

I'm afraid I'm not going to give a full explanation here, but the nub
of the matter is as mentioned above.

>>a) When you want to explain the imperative heapsort
>>b) When you know that the data are going to be in an order that is bad for
>>   mergesort (take n . concat . repeat) [0,1] for example

Here's a practical comparison (using Hugs 1.3) between your mergesort
as corrected above, and my heapsort as originally sent:

? :gc
Garbage collection recovered 995633 cells
?  (length . mergesort . concat . take 5000 . repeat) [0,1]
1
(769128 reductions, 1260406 cells, 1 garbage collection)
? :gc
Garbage collection recovered 995633 cells
?  (length . heapsort . concat . take 5000 . repeat) [0,1]
1
(388900 reductions, 813056 cells)

and with data designed to make comparisons dominate:

? (length . mergesort . concat . take 5000 . repeat) ["aach","aagh"]
1
(5467874 reductions, 10727534 cells, 155 garbage collections)
? (length . heapsort . concat . take 5000 . repeat) ["aach","aagh"]
1
(2236721 reductions, 4540208 cells, 67 garbage collections)
? 

>>c) when you are worried about the worst-case behaviour more than the average
>>   case

As I said originally, mergesort is somewhat faster in the average case.

-- 
Jon Fairbairn [EMAIL PROTECTED]
18 Kimberley Road[EMAIL PROTECTED]
Cambridge CB4 1HH  +44 1223 570179 (pm only, please)







Re: Heap Sort

1997-10-01 Thread Jon . Fairbairn

Here is my version:

First we need treefold:

---
module Treefold where

-- I'm surprised treefold isn't in the standard prelude since it's so useful
-- treefold (*) z [a,b,c,d,e,f] = (((a*b)*(c*d))*(e*f))

-- translated from the version I wrote in Ponder in October 1992
-- Jon Fairbairn

treefold f zero [] = zero
treefold f zero [x] = x
treefold f zero (a:b:l) = treefold f zero (f a b: pairfold l)
 where pairfold (x:y:rest) = f x y: pairfold rest
   pairfold l = l -- here l will have fewer than two elements

--

module Heapsort where
import Treefold

-- translated from the version I wrote in Ponder in October 1992
-- Jon Fairbairn

data Heap a = Nil | Node a [Heap a]
heapify x = Node x []

heapsort :: Ord a => [a] -> [a]

heapsort = flatten_heap . merge_heaps . map heapify

where merge_heaps :: Ord a => [Heap a] -> Heap a
  merge_heaps = treefold merge_heap Nil

  flatten_heap Nil = []
  flatten_heap (Node x heaps) = x:flatten_heap (merge_heaps heaps)

  merge_heap Nil Nil = Nil
  merge_heap heap@(Node _ _) Nil = heap
  merge_heap node_a@(Node a heaps_a) node_b@(Node b heaps_b)
 | a < b = Node a (node_b: heaps_a)
 | otherwise = Node b (node_a: heaps_b)

-- end


On 21 Sep , Chris Dornan wrote:
> When would a heap sort be preferable to a merge sort?

a) When you want to explain the imperative heapsort
b) When you know that the data are going to be in an order that is bad for
   mergesort (take n . concat . repeat) [0,1] for example
c) when you are worried about the worst-case behaviour more than the average
   case

Most of the time, mergesort with a phase that breaks the input into
runs will be faster.  However, it's possible to write a heapsort that
starts with a run phase; this is slightly slower than mergesort for
the average case, but the worst case is better.

  Jon

-- 
Jon Fairbairn [EMAIL PROTECTED]
18 Kimberley Road[EMAIL PROTECTED]
Cambridge CB4 1HH  +44 1223 570179 (pm only, please)









Re: Heap sort

1997-09-20 Thread Jon . Fairbairn

On 19 Sep, Nicholas Bleakly wrote:
> Does any body have a heap sort algorithm (i.e. takes a single unsorted
> list and applies a heap sort to it)?

If you mean a functional one, I have.  I could email it to you. Or
post it here if wanted.  Does anyone else have one?

-- 
Jon Fairbairn [EMAIL PROTECTED]







Re: Heap Sort

1997-10-07 Thread Jon . Fairbairn

On  4 Oct , Chris Okasaki wrote:
> But the heapsort you give is nothing like the standard imperative
> heapsort! 

Point taken, although I think 'nothing like' is overstating the case.

> Yes, it uses a heap, but not the binary heap used by standard
> heapsort.

Perfectly true. I only said that you could use my version when
explaining it, not that it would be suitable for the whole
explanation.  What I had in mind was that this sort is easier to
explain, and gets some of the concepts across.  Most of the
complication in imperative heapsort is to do with keeping the heaps in
place in a fixed size array.

> Larry Paulson's "ML for the Working Programmer" includes a
> functional heapsort ... is probably superior for pedagogical
> purposes.

Well, I'd certainly want to go on to describe this in our hypothetical
pedagogical situation :-) Mind you, I haven't done any teaching since
I got ill (which was before I wrote the sort), so I have no
experimental evidence.  The approach above might just prove confusing.

Perhaps I should just have said that a use for it is as an answer to
people who say it's difficult (or impossible) to write a heapsort
functionally, which was what prompted me to write it in the first
place.

> [1] Fredman, Sedgewick, Sleator, and Tarjan.
> "The pairing heap: A new form of self-adjusting heap"
> Algorithmica 1(1):111-129, 1986.

Many thanks for this reference, of which I was unaware.

  Jon

-- 
Jon Fairbairn [EMAIL PROTECTED]
18 Kimberley Road[EMAIL PROTECTED]
Cambridge CB4 1HH  +44 1223 570179 (pm only, please)







group, groupBy

1997-10-10 Thread Jon . Fairbairn

On  8 Oct , Ralf Hinze wrote:
> Merge sort has O(n log n) running time independent of the input.
> However, it is easy to make merge sort smooth by dividing the input
> into increasing runs. Carsten suggests to use `group (<=)' which only
> takes increasing runs into account.

... and also doesn't work!  
> group :: Eq a => [a] -> [[a]]

well, unfortunately we also have

? groupBy (<=) [1,2,3,4,5,1,2,3] == [[1, 2, 3, 4, 5, 1, 2, 3]]

What I want to know is whether the members of the mailing list thing
this is the right behaviour for groupBy.  In the List library it's
written using span, which obviously won't give the behaviour Carsten
intended and which I think is the more natural.  ie groupBy op ought
to return a list of lists where each member is in order under `op`.

Is there some good technical reason why we want the present groupBy?

  Jon

-- 
Jon Fairbairn [EMAIL PROTECTED]
18 Kimberley Road[EMAIL PROTECTED]
Cambridge CB4 1HH  +44 1223 570179 (pm only, please)







Worst case for multipass pairing sort

1997-11-11 Thread Jon . Fairbairn

Egg on face time for me: I've claimed that the worst case for
multipass pairing sort (Ralf Hinze named this 'jonssort', but I'm not
keen on that - I'll call it mpp_sort here) had better worst case
performance than merge sort.  Unfortunately I hadn't worked out the
worst case correctly.

I had thought that 
> bad4merge n = take n (wcm m 1 m []) where
>  m = least_power_of_2_not_less_than n
>  wcm 0 l h acc = acc -- This never happens?
>  wcm 1 l h acc = h: acc
>  wcm 2 l h acc = h: l: acc
>  wcm n l h acc = wcm mid l h (wcm (n - mid) (l + mid - 1) (l + n - 2) acc)
>  where mid = n `div` 2
> 
> least_power_of_2_not_less_than n = lptbt n 1
>where lptbt n p = if p >= n
>  then p
>  else lptbt n (2*p)

which generates one of the worst cases for merge was also worst for
mpp_sort.  Having thought about it a bit more I came up with
 
> bad4mpp n = take n (wch m 1 1) where
> m = least_power_of_2_not_less_than n
> wch 0 _ _ = []
> wch 1 i s = [i]
> wch n i s = (wch h (i) (2*s)) ++ (wch h (i+s) (2*s))
> where h = n `div` 2

Using versions of the sorts that count the number of comparisons, I
get the following results:

for bad4merge 1000, 
plain mergesort takes 8985 comparisons where mpp_sort takes 2769

but for bad4mpp 1000
mergesort takes 8983 but mpp_sort takes 12606

Back to the drawing board.

I'd be interested in the results for these particular cases from other
sorts, and also if someone could come up with real worst cases for
each sort.  Also interested to see closed versions of the above
functions - my brain is too foggy to work them out myself.

  Jon

-- 
Jon Fairbairn [EMAIL PROTECTED]
18 Kimberley Road[EMAIL PROTECTED]
Cambridge CB4 1HH  +44 1223 570179 (pm only, please)










What's best for Dynamic GUIs?

1997-11-22 Thread Jon . Fairbairn

I'm thinking of playing with writing some interactive
graphical/animated programmes - so which is the best system to use?

Looking at their web pages, I see
haggis last release Apr 96
fudgets last release Nov 96
Fran recent

but Fran needs Windows stuff and I want to run on Linux + X
windows. I'm currently using ghc 2.08, and Haggis which might be the
obvious choice dates from before that release.  Is any work going on
with either Haggis or Fudgets to make them work with Haskell 1.4?

As far as opinions on which is best are concerned, I'd prefer to hear
from people who have tried more than one of the above, rather than
from the developers.


  Jon

-- 
Jon Fairbairn [EMAIL PROTECTED]








Re: standard Haskell

1997-12-11 Thread Jon . Fairbairn

On 11 Dec, Paul Hudak wrote:
> I suppose that one improvement that you'd like and that I agree would be
> an improvement is the ability to mark messages as read. 

With Netscape Navigator (at least on Linux) you can set an option not
to expire visited links.  This means they change colour and stay that
way indefinitely.  I think 'indefinitely' here means 'until something
goes wrong with nerdscaphe'.

I suppose John could implement something using cookies, but why should
he put in so much effort?

  Jon

-- 
Jon Fairbairn [EMAIL PROTECTED]








Re: Standard Haskell Libraries

1998-04-24 Thread Jon . Fairbairn

On 24 Apr, Frank A. Christoph wrote:
> Suggestion for Standard Haskell:
> 
> Copy all the stuff in the Prelude to the standard libraries, at least when
> there is an obvious module for them to go to. 

Hear here! (or is that here, here or hear hear?)  That was on my list
to suggest to the standard Haskell committe - let's hope some of them
are listening.

 Jon

-- 
Jon Fairbairn [EMAIL PROTECTED]







Re: let succ be an Enum class member

1998-05-12 Thread Jon . Fairbairn

On 12 May, Jeffrey R. Lewis wrote:
> I agree, in fact, I'd go one stronger.  I'll propose that `fromEnum' and
> `toEnum' be taken out, since clearly not all enumerable types are
> subtypes of Int (as you point out, Integer leaps immediately to mind).

An alternative would be to return fromEnum and toEnum to their
overloaded types:

toEnum   :: Integral i => i -> a
fromEnum :: Integral i => a -> i

would that suit?

-- 
Jon Fairbairn [EMAIL PROTECTED]







Syntax dubion

1998-06-26 Thread Jon . Fairbairn

if I write

(a &&& b) x = a x && b x

hugs accepts it, but ghc rejects it.  I think that ghc is correct in
that the report only allows 

 funlhs 
-> 
   var apat {apat } 
| 
   pati+1 varop(a,i) pati+1 
| 
   lpati varop(l,i) pati+1 
| 
   pati+1 varop(r,i) rpati 

ie no () and no extra arguments, but given that one may want to define
higher order functions this way, we ought to make the language allow it.

Can anyone argue against it?

-- 
Jon Fairbairn [EMAIL PROTECTED]
18 Kimberley Road[EMAIL PROTECTED]







Empty arrays

1998-06-30 Thread Jon . Fairbairn

Another little quibble:

If I run the following

> module Main where
> import Array

> main = (putStr . show . bounds . array (0,-1)) ([]::[(Integer,Char)])

with ghc I get (0, -1), but with hugs I get 

Program error: index: Index out of range

As far as I can interpret the library report, ghc is correct in this
respect.  Moreover, I think that is what we should get, since an empty
array is useful.  So perhaps I should simply be reporting a bug in
hugs, but I thought I'd check here to be sure that everyone agrees
that this is correct.

   Jon

-- 
Jon Fairbairn [EMAIL PROTECTED]







simple interface to web?

1998-07-10 Thread Jon . Fairbairn

I'm interested to hear what other people think of providing a uniform
interface to URLs and files as a standard part of the IO library.

What I have in mind is adding a function openURL that returns a
handle, access to which starts a fetch to a disk buffer, and make sure
that hClose on such a handle aborts any continuing fetch.

Obviously sophisticated web access would require a more complex
interface, but there is a class of programme for which nothing more is
necessary. Like directory handling the more sophisticated stuff would
go in a different library. If this were part of Standard Haskell I
think it would usefully increase the appeal of the language.

Any thoughts?

-- 
Jon Fairbairn [EMAIL PROTECTED]








Re: simple interface to web?

1998-07-13 Thread Jon . Fairbairn

On 13 Jul, S. Alexander Jacobson wrote:
> You should look at Cardelli's paper on Service Combinators.  
> I don't have a URL handy, but you should be able to find it with a quick
> search.

http://www.luca.demon.co.uk/Papers.html#ServiceCombinators> (the
links to the contents of the paper are at the top of this document).
This is very interesting, and is probably a useful start for the
definition of the _sophisticated_ web library.  I still think that
there is a marketing case for putting openURL (which would correspond
to Cardelli & Davies' url function) in the standard library (together
with some extra exceptions for things such as connexion timed out and
so on).

-- 
Jon Fairbairn [EMAIL PROTECTED]
18 Kimberley Road[EMAIL PROTECTED]
Cambridge CB4 1HH  +44 1223 570179 (pm only, please)







Re: GHC/Hugs Status (was Re: simple interface to web?)

1998-07-14 Thread Jon . Fairbairn

On 14 Jul, S. Alexander Jacobson wrote:
> I definitely agree that Haskell should have network primitives in the
> standard library, but doesn't this have to wait until the whole exceptions
> issue is resolved?  

I don't think so - all exceptions to do with net protocols can (be
deferred until they can be) handled via the extant IO exceptions
mechanism.

> As such, it seems tough to
> write libraries right now as the upcoming GHC/Hugs release will contain
> features that strongly affect library design:
> 
> * multi-parameter type classes

etc... all seem to be things that are waiting 'till Haskell 2.  My
point was that _something_ should be in Standard Haskell.  The features
you mention are likely to help when writing a better network library,
but let's not get distracted from the option of including something
straightforward in the standard.

Not that there's anything wrong with wanting Haskell 2 to happen
swiftly too!

  Jon

-- 
Jon Fairbairn [EMAIL PROTECTED]
18 Kimberley Road[EMAIL PROTECTED]
Cambridge CB4 1HH  +44 1223 570179 (pm only, please)






Re: GHC/Hugs Status (was Re: simple interface to web?)

1998-07-16 Thread Jon . Fairbairn

On 15 Jul, Simon L Peyton Jones wrote:
> I hadn't realised that your suggestion was a propos of Standard
> Haskell.
> 
> I'm pretty leery about trying to agree any new libraries at this
> stage, unless someone comes up with a worked-out, and implemented,
> specification pretty quickly.  The name of the Std Haskell game
> is rapid closure. 

I hope it doesn't close too quickly!

> There are just tons of things that 'ought' to be in it that aren't
> going to be.

But if there are too many things missing, no one will use Standard
Haskell - it already seems as if most of the people on this list are
going to go straight to Haskell 2, which would mean that Standard
Haskell might only be used for teaching.

Maybe it's too soon to put an openURL action in (though I would have
thought this could be specified pretty easily), but I really think
that the tidying up of the relationship between the prelude and the
standard libraries is vital. For example, I can see no reason why
PreludeIO and IO should be separate.  Surely it wouldn't be much work
to put it all in the IO library? As it stands, the prelude has to
refer to the library, which, I think, underlines the inconsistency:

As far as I can tell, the only prelude operations on IOError are show
and (=), so to tell what a [system raised] error is you have to import
IO. (Although you can catch errors without looking at them or tell if
a new error is the same as an earlier one!)


I'd also like to observe that fitting Haskell 2 with Standard Haskell
ought to be easier if less is in the Prelude and more in libraries.

  Jon

-- 
Jon Fairbairn [EMAIL PROTECTED]
18 Kimberley Road[EMAIL PROTECTED]
Cambridge CB4 1HH  +44 1223 570179 (pm only, please)







RE: Monomorphism

1998-07-21 Thread Jon . Fairbairn

On 21 Jul, [EMAIL PROTECTED] wrote:
> 
> I'm going to ask a very stupid question.

not stupid, actually quite subtle!

> Why on earth is len computed twice in this example?  I really don't   
> understand this!

I think the confusion arises from the use of the terms poly- and mono-
morphism to refer both to type variables that are genuinely
polymorphic, and to those that are restricted to a collection of class
instances. Simon's example is a little unhelpful in this regard:

>  f xs = if len > 3 then len else 0
>   where
>   len = length xs

lurking here is the fact that len > 3 requires the computation of an -
whatever the default integral type is, let's say - Int, whereas the
len that is returned _may_ be of some other Integral type.  In the
case where the result is also used as an Int, there is no _need_ to
recompute it (and a compiler might produce appropriate code or not),
but if the context requires Integer, the computation would have to be
done again (if there were more than maxint elements in the list, at
any rate!)

The example might be more convincing if the relationship between the
various possible instances were more arbitrary - in the case of
Integral we can think of computing at Integer and converting at the
end, an option that is not necessarily available.

Incidentally, length :: Integral a => [b] -> a, I think.

   Jon


-- 
Jon Fairbairn [EMAIL PROTECTED]







Re: Rambling on numbers in Haskell

1998-08-03 Thread Jon . Fairbairn

On  3 Aug, Jan Skibinski wrote:
>> How hard is it to write "import Complex"?
>> 
> 
>   Not hard at all, but I think I did not make myself
>   clear in my previous post. Here is the clarification:
> 
>   One of the benefits of having Complex closely coupled
>   with other numbers

That of itself is not an argument for its inclusion in the language
core rather than in a library.  I think that there is a general
agreement that the number hierarchy needs an overhaul, which could go
a long way towards adressing your complaints.

> is its potential utilization in error handling.

> So far, evaluation of sqrt (-1) produces unrecoverable error.

I think that there is some confusion wrt types here.  If you are
hoping for a floating answer, sqrt (-1) has to produce an error.
While in some cases a Number type (like Miranda) may be useful, I
think the 'proper' solution in most cases is to make the types of
things like sqrt overloaded to reflect their properties.

so sqrt :: (Numeric n, Floating f) => n -> f

>   Not only sqrt, but a bunch of other functions could be
>   rescued in a similar way:
> 
>   log (-1)

same overloading as sqrt, then

>   asin (4/3) - currently interpreted as Floating, produces NaN

different issue (press the button on Kent for details ;-)

>   Anyone can design a complex number library. The task is
>   not much more complex (pun intended:-) than dsigning
>   the type Point.
>   What is difficult though is to make Complex a citizen
>   of the world of existing numbers.

Right, but it should be done via a class hierarchy, not by squishing
all the numbers into one type.

-- 
Jon Fairbairn [EMAIL PROTECTED]







Re: Rambling on numbers in Haskell

1998-08-03 Thread Jon . Fairbairn

On  3 Aug, [EMAIL PROTECTED] wrote:
> so sqrt :: (Numeric n, Floating f) => n -> f

whoops!  I meant to say 
sqrt :: (Numeric n,  Numeric f) => n -> f

or something - the important bit was that the result type shouldn't be
constrained to be the same as the argument, because while sqrt int is
meaningful it doesn't usually give an int result.  What you get back
should depend on what you use it for.

-- 
Jon Fairbairn [EMAIL PROTECTED]
18 Kimberley Road[EMAIL PROTECTED]
Cambridge CB4 1HH  +44 1223 570179 (pm only, please)







Re: Felleisen on Standard Haskell

1998-08-04 Thread Jon . Fairbairn

On  4 Aug, Philip Wadler wrote:
>   I would be happy to find a name
>   that was less grand and final-sounding than 'Standard Haskell' though;
>   but more final sounding than 'Haskell 1.5'.
> 
> Actually, Haskell 1.5 sounds exactly like what you want: halfway
> between the first draft and the next edition.  It also resonates
> with those of use who remember Lisp 1.5, which was the `Standard
> Lisp' for many years.  -- P

I think I agree; the other alternative would to be literal and call it
Haskell 1 Final, or 1F for short.


-- 
Jon Fairbairn [EMAIL PROTECTED]







Re: some Standard Haskell issues

1998-08-07 Thread Jon . Fairbairn

On  7 Aug, [EMAIL PROTECTED] wrote:
> * maximal munch and comments
> 
>   Explicitly allowing operators such as --- and --> is not just
>   a clarification; it is a change in the comment convention. (cf. p8 of
>   the 1.4 report `The sequence -- immediately terminates a symbol ...')

right, and a positive change because it would remove this special case
from the report

>   Though it is attractive to allow a wide range of operator symbols

it's not just convenient: try putting yourself in the mindset where
you want an arrow and have chosen --> so as not to clash with ->, and
then interpret the error messages you get.  It's an ugly irregularity.

>   --- comment

unambiguously not a comment

>   --

likewise
>   Any change putting in doubt (or even preventing) the commenthood of
>   an unbroken line of 2 or more dashes would be a pain.

only a pain, and only briefly.  I contend that it's easier to learn to
write

-- ---

than to learn not to try to define -->, |--, --| and so on.  Oh, and what is

{-- comment --}

under the present rules?

  Jon


-- 
Jon Fairbairn [EMAIL PROTECTED]







Re: Int vs Integer

1998-09-10 Thread Jon . Fairbairn

On  9 Sep, John Launchbury wrote:
> When we discussed this before I appealed for someone to try it out and
> report on the results:
> * What slowdowns (?speedups) can be expected in practice using Integer
>   rather than Int?
> * Do existing programs break wildly with this more general type, or
>   do they work just as before? Or do they still work but now produce
>   different answers than before.
> 
> Please can someone who feels strongly that we should make these changes
> perform some experiments and report the results.

Re speed: please don't!  I don't see how knowing about the speed of
existing implementations can affect the reasoning in deciding to make
the change. As far as I know, none of the existing implementations
takes the speed of Integer seriously (ghc certainly doesn't), so the
data obtained would be thoroughly misleading.  Furthermore, in a new
programme it would not be hard to decide where to use Int if one is
worried about speed. In an old programme discovering that it runs
slowly in Haskell 1.5 would not occasion terribly much work either -
you just have to change the import declarations to get hold of
specially defined versions of the relevant functions.  I'd agree that
it might be useful to provide a compatibility prelude with
implementations of 1.5.

As to the second point, if old programmes produce different results,
surely that's going to be because they were wrong in the first place!
If they don't compile, it's harmless.

So I don't think either of these experiments would be helpful.
Changing to Integer improves the design of the language and increases
the chance that programmes will give correct results. It's not as if
we are asking for Int to be banned!


  Jon


-- 
Jon Fairbairn [EMAIL PROTECTED]
18 Kimberley Road[EMAIL PROTECTED]
Cambridge CB4 1HH  +44 1223 570179 (pm only, please)







Re: Int vs Integer

1998-09-10 Thread Jon . Fairbairn

On 10 Sep, Will Partain wrote:
> [EMAIL PROTECTED] writes:
> 
>>  As far as I know, none of the existing implementations
>> takes the speed of Integer seriously (ghc certainly doesn't), ...
> 
> The GHC implementation has always been a thin wrapper on top
> of the GMP (GNU multi-precision arithmetic) library.  So,
> while we may not have taken Integer performance too
> seriously, we made a point of hanging around with people who
> did.  (Hey, Lennart made much the same choice, and he's not
> one to give away speed for nothing :-)

The question is of performance for Int sized things in Integer, so the
fact that you call a good library isn't relevant; what's important is
what you do when you don't _need_ to use GMP to get the answer.  My
guess is that most of the real cost of doing Int sized arithmetic in
Integers is the cost of detecting overflow.  


-- 
Jon Fairbairn [EMAIL PROTECTED]
18 Kimberley Road[EMAIL PROTECTED]
Cambridge CB4 1HH  +44 1223 570179 (pm only, please)






Re: Int vs Integer

1998-09-14 Thread Jon . Fairbairn

On 13 Sep, Simon Marlow wrote:

> The common case of applying a dyadic operation to small Integers would
> then be pretty close in performance to that of Int (a couple of
> indirect jumps, and a test/branch for the overflow detection, to be
> precise).

Now that's more like what I had in mind. Isn't it also possible to
reduce the number of checks for sequences of operations?

-- 
Jon Fairbairn [EMAIL PROTECTED]
18 Kimberley Road[EMAIL PROTECTED]
Cambridge CB4 1HH  +44 1223 570179 (pm only, please)






Fwd: Re: Int vs Integer

1998-09-15 Thread Jon . Fairbairn

Bother!  Sent this only to Simon...
-- Forwarded message --
From: [EMAIL PROTECTED]
 Subject: Re: Int vs Integer
Date: Tue, 15 Sep 1998 18:15:01 +0100 (BST)
  To: [EMAIL PROTECTED]

On 15 Sep, Simon Peyton-Jones wrote:
> I think there is one powerful argument for retaining the status quo,
> but it is one no one has commented on: overloaded types can give
> rise to strange error messages that bite beginners.

I think that is mainly a question of designing good error messages.
If there is only one alternative in scope, it should be possible to
give helpful hint, for example.  There is also nothing to stop a
teacher providing a library where things are specialised if this is
still a problem.  Phil's remarks are also to the point.

> After all, we have just *un-overloaded* map and friends for just
> this reason.

I think that was a mistake, given my above observations.

>   - generalise length, splitAt, drop, take, replicate
>   - generalise toEnum, fromEnum
>   - leave (!!) alone (arrays must fit in an address space)

True, but worry about the knock-on effect of using a variable in an
index to an array, causing other expressions to be typed at Int.
Overload that too!

Given that the report already mentions the 'specialize' pragma, I
don't see any reason why the newly overloaded functions shouldn't be
accompanied by specialisations for both Integer and Int, which should
remove the efficiency drawback of making this change.


  Jon

-- 
Jon Fairbairn [EMAIL PROTECTED]









Re: Int vs Integer

1998-09-24 Thread Jon . Fairbairn

On 15 Sep, Hans Aberg wrote:
>   The generalization of the Int type, as I see it, is a binary type, a
> sequence of bit of fixed length, which has special operations such as
> right/left shift with under/overflow, rotations, signed/unsigned arithmetic
> and Boolean bit operations.

agreed, though I think there is a strong case of providing most of
those operations on Integer too (perhaps at a different type).

-- 
Jon Fairbairn [EMAIL PROTECTED]







Re: Int vs Integer

1998-10-05 Thread Jon . Fairbairn

On  4 Oct, Chris Dornan wrote:
> As a plain, ordinary punter could I ask for one of two things:
> 
>1) More or less kill Int as a general-purpose type and adopt unbounded
>   integers (Integer) as the standard integral type.  If you do this then
>   please put
> 
>   type Int = Integer
> 
>   into the standard prelude.

I don't understand this.  For old programmes, the right thing to do
would surely be to use the compiler to determine which modules require
the addition of "import Int", and if the standard prelude has the
above declaration, wouldn't it make it harder?  Probably one would put
an explicit "default (Int)" in all the modules, which doesn't seem too
much of a hardship.

>   For those that need old-fasioned efficient, bounded integers these can be
>   provided in a separate library module.
> 
>   As has been said by others, would those that would like to see Int
>   knocked on the head make sure that the performance hit won't be too
>   severe. 

The above statements appear to be in conflict.  The object of the
change is to make sure that the default behaviour is safe rather even
if less efficient.  When the efficiency hit is significant and the
programmer is sure that Int is safe, Int would be used.

Am I missing the point here?

  Jon

-- 
Jon Fairbairn [EMAIL PROTECTED]
18 Kimberley Road[EMAIL PROTECTED]
Cambridge CB4 1HH  +44 1223 570179 (pm only, please)










RE: MonadZero (concluded?)

1998-11-05 Thread Jon . Fairbairn

On  5 Nov, Simon Peyton-Jones wrote:
>  I don't like grabbing too many very generic names like zero, plus, fail
>  from the user (this is all in the Prelude, remember).  I don't want
>  to grab 'raise' because we're going to want it for exceptions in Haskell
>  2.  I havn't been able to think of anything better than these monsters.

um, monadZero, monadFail?  People who can't type can always add their
own renamings.

-- 
Jon Fairbairn [EMAIL PROTECTED]







Re: derive conflicts with multiply-defined and module level import

1998-11-07 Thread Jon . Fairbairn

On  7 Nov, Erik Meijer wrote:
>  >Another reason is that allowing definitions to be split up
>  >without any special syntax indicating this would harm readability.
[...]
>  
>  This is *exectly* the reasoning I am opposed to. It is not to the language
>  designer to decide for me what is readable of not!

 Oh yes it is! *

I think there is a strong case for making this (and some, but not all
other similar issues) part of the language.  In the first instance it
reduces (ideally removes?) the need for local style-checking
preprocessors.  If I read a Haskell programme at the moment, I can be
sure when I've seen the last clause.  If this were changed I'd need a
preprocessor to tell me that this sensible grouping had been
preserved. (Conventions are typically flouted unless eforced by the
compiler.

In the second instance, there is cause to believe that (good)
programming language designers _do_ know better than the typical
programmer.  At least we should!  (Erik: remember that you aren't a
typical programmer when you argue these things.) Typical programmers
misinterpret the results of readability research:

 Me: "Why have you got _so_many_ blank lines in your programme?

 Prog: "Blank lines improve the readability of code."

 Me: "But there's so much space that you can't see a whole definition
  at a time."

 Prog: "Research has shown that the more blank lines there are, the
more readable the code"

 Me: "!"


>  Erik "warrior against the Edith Bunkerizing of programming

Who she?

>  languages" Meijer

  Jon

* apologies to those not familiar with the British pantomime traditions.

-- 
Jon Fairbairn [EMAIL PROTECTED]








Re: Haskell 98 progress...

1998-11-23 Thread Jon . Fairbairn

On 23 Nov, Graeme Moss wrote:
>  
>  So no one minds that `--(Nothing)' is a comment whereas `--?Nothing?'
>  is not a comment? 

I think that this highlights the fact that the top-bit-set characters
were put into the language with relatively few distinctions; ASCII
brackets (){}[] are not included in symbol, but those in the rest of
unicode are (ambiguously; "Any unicode symbol or punctuation" seems to
include ? to me). I don't think Haskell 98 should do anything about
this.

>  And that `--Copyright 1998' is a comment whereas `--? 1998' is not a
>  comment? 

While I might regard the first of these as bad style, I don't have any
difficulty seeing that the second is not a comment.  People used to
lisp might be irritated by the error messages they get from things like 

tree-reduce f t = whatever

but given that Haskell allows symbols to be adjacent, I think the new
comment rule is correct.


>  Or that sequences like `--?What' and `--!Wow' are not comments?

Grammatically and typographically nasty anyway!

>  I had to consult the syntax report in order to determine whether these
>  were comments or not...  at least with the old system I could tell
>  immediately.

I think that's just a matter of getting used to it.  The new rule makes
the lexemes --, ---, , ... into comment introducers and treats -
the same as other characters otherwise (unless I'm mistaken!), so it's
easier for someone to see that 

  a --> b

is an expression now.  The previous rule was visually confusing.

>  Apologies if this is dragging up old arguments. 

Likewise!

-- 
Jon Fairbairn [EMAIL PROTECTED]







Re: FW: Why I hate n+k

1998-11-27 Thread Jon . Fairbairn

On 27 Nov, Simon Marlow wrote:

>   (((+) + 1) + 1) 1 = (+)

I just read this out to a friend, whose response was "Show that sort of
thing to hackers and you'll convert them to functional programming
instantly!"



-- 
Jon Fairbairn [EMAIL PROTECTED]







Re: Type casting??

1999-03-11 Thread Jon . Fairbairn

On 10 Mar, Steve Frampton wrote:
>  My function looks sort of like this:
>  
>foo :: Int -> [a]
>foo 0 = []
>foo x = ['1'] ++ foo(x - 1)

Since Haskell can infer types most of the time, try

>foo 0 = []
>foo x = ['1'] ++ foo(x - 1)

with this loaded into hugs you can then try

Main> :type foo
foo :: Num a => a -> [Char]
Main> 

which tells you the correct type.  The type you declared is too
general, because it means that foo would have to have the property that
whatever type of list was wanted in a given context, (foo n) would have
to return a list of that type.  But your foo returns a list of
characters, so clearly doesn't satisfy this.

The "Num a =>" indicates that the argument has to be a number; this is
inferred because you subtract one from it.

you could write

foo 0 = []
foo x = ['1'] ++ foo ((x::Int) - 1)

which gives

Main> :type foo
foo :: Int -> [Char]
Main> 

or write

foo :: Int -> [Char]
foo 0 = []
foo x = ['1'] ++ foo (x - 1)

to declare it yourself.

Note that type casting in the C sense is not available in Haskell,
the only thing you can do is to restrict something to have fewer types
than it otherwise would have.

  Jon

-- 
Jon Fairbairn [EMAIL PROTECTED]
18 Kimberley Road[EMAIL PROTECTED]
Cambridge CB4 1HH  +44 1223 570179 (pm only, please)







Re: View on true ad-hoc overloading.

1999-05-20 Thread Jon . Fairbairn

On 20 May, Kevin Atkinson wrote:
>  Sorry typo.  That should be optional.

Is this a job for overloading?  I think it would be better to provide
some syntactig sugar and compile-time checks for something like this:

data Argtype = Arg {a::Int, b::Bool, c::Char}
arg = Arg {a = 1, b = True, c = error "c mandatory"}

f (Arg _ True c) = c
f (Arg n False c) = head (show n)

main = putStr (show (f $ arg {c = 'c'}))


>  It should be.
>  
>  array (range 1 to 10) [(1,1), (1,2) ]
>  array (range 1 to 10 skip 2) [(1,1), (3,2) ...]
>  array (range 1 to 100 factor 2] [(1,1), (2,2), (4,3), (8,4) ...]
>  
>  Perhapes range is not a good word to use.  Maybe indices instead.

I don't see what you are getting at here. 'array' takes a list as an
argument.

-- 
Jón Fairbairn [EMAIL PROTECTED]
18 Kimberley Road[EMAIL PROTECTED]
Cambridge CB4 1HH  +44 1223 570179 (pm only, please)






RE: Proposal: Substring library for Haskell

1999-05-20 Thread Jon . Fairbairn

On 20 May, Frank A. Christoph wrote:
>  
> > > I would welcome either. However, there is a huge body of code that
> > > assumes strings are lists of chars.
>  >
> > Yes, obviously... this is for new programs (which people aren't writing
> > because of Haskell's inefficiency in dealing with strings).
>  
>  While I think Haskell should also support primitive random-access strings,
>  String as [Char] is not all that inefficient for many purposes, thanks to
>  laziness. After all, the world's most famous text-processing language, Perl,
>  represents strings as character lists too.

I think the reall absence here is a standard string processing library
for strings of any type whatever.  The first step would be to put one
together for [Char], surely?  While it makes sense to think about
alternative representations at the outset (and possibly use them
internally), the absence of a full-featured string processing library
is more of an obstacle than it's lack of efficiency.

-- 
Jón Fairbairn [EMAIL PROTECTED]
18 Kimberley Road[EMAIL PROTECTED]
Cambridge CB4 1HH  +44 1223 570179 (pm only, please)






Re: Language Feature Request: String Evaluation

1999-06-08 Thread Jon . Fairbairn

On  8 Jun, Paul Hudak wrote:
>  show x should be a string that when printed looks like the value that
>  you would have to type to generate it directly.  This example is most
>  instructive:

[...]

and this is just cute:

main = putStr (quine q)
quine s = s ++ show s
q = "main = putStr (quine q)\nquine s = s ++ show s\nq = "

-- 
Jón Fairbairn [EMAIL PROTECTED]
18 Kimberley Road[EMAIL PROTECTED]
Cambridge CB4 1HH  +44 1223 570179 (pm only, please)







Re: Deriving Enum

1999-07-13 Thread Jon . Fairbairn

On 11 Jul, Wolfram Kahl wrote:
>  Koen Claessen <[EMAIL PROTECTED]>
>  proposes the following diagonalisation function:
>   > 
>   >   [ (a,b) | (a,b) <- [1..] // [1..] ]
>   > 
>   > For a suitable definition of (//), for example:
>   > 
>   >   (//) :: [a] -> [b] -> [(a,b)]  
>   >   xs // ys = diagonalize 1 [[(x,y) | x <- xs] | y <- ys]
>   >where
>   > diagonalize n xss = 
>   >   xs ++ diagonalize (n+1) (xss1 ++ xss2)
>   >  where
>   >   (xs,xss1) = unzip [ (x,xs) | (x:xs) <- take n xss ]
>   >   xss2  = drop n xss
>   > 
>   > And it works for any type.
>  
>  The core function here is
>  
> > (diagonalize (1 :: Integer)) :: [[a]] -> [a]
>  
>  This function diagonalises finite or infinite lists
>  with arbitrary finite or infinite element lists.
>  
>  
>  To me, it seems unsatisfactory to have a solution to this pure list problem
>  with auxiliary functions relying on integers.

I got rather lost in the ensuing discussion, so I've composed this
reply from back here.  It seems to me that the core function is (//),
which can be written like this:

> module Diagonalise ((//)) where
> import List

A diagonalisation function that doesn't use numbers.

> (//):: [a] -> [b] -> [(a,b)]

> a // b = diag a b []

the third argument acc is an accumulator for the reversed initial
segment of a ie reverse acc ++ a == a0

> diag [] b [] = []

> diag [] [] acc = []

> diag [] (b: bs) acc = zip acc bs ++ diag [] bs acc

> diag (a: as) b acc = zip acc' b ++ diag as b acc'
>  where acc' = a: acc


Or have I totally lost it?
-- 
Jón Fairbairn [EMAIL PROTECTED]
18 Kimberley Road[EMAIL PROTECTED]
Cambridge CB4 1HH  +44 1223 570179 (pm only, please)






Re: Deriving Enum

1999-07-13 Thread Jon . Fairbairn

On 13 Jul, Wolfram Kahl wrote:
>  I confess guilty to have diverged from this simpler problem
>  
> > (//) :: [a] -> [b] -> [(a,b)]
>  
>  to the more general problem
   ???


like 

> diagonalise:: [[a]] -> [a]
> diagonalise l = d [] l


> d [] [] = []

> d acc [] = --  d [] acc would do, but muddles the order;
>heads acc ++ d (rests acc) []

> d ls (l1:rest) = heads (ls') ++ d (rests ls') rest
>  where ls' = l1: ls


> heads l = [a | (a: _) <- l]

> rests l = [as | (_: as) <- l]


?

Incidentally, are there standard names for 'heads' and 'rests' as I
have them above?  I couldn't find them.

  Jón
  
-- 
Jón Fairbairn [EMAIL PROTECTED]
18 Kimberley Road[EMAIL PROTECTED]
Cambridge CB4 1HH  +44 1223 570179 (pm only, please)








Student project: error messages (was RE: Question)?

1999-08-20 Thread Jon . Fairbairn

On 19 Aug, Mark P Jones wrote:
>  [...] note that the error messages that prompted
>  Jon's comment didn't have anything to do with sophisticated type systems.
>  Dealing with those kinds of things requires some hard work, but it isn't
>  research, and so it's hard to justify, at least in an academic context.

This was my thought exactly, but it occurs to me to wonder whether it
might not form an interesting undergraduate (or early graduate)
project.  The idea would be to instrument hugs to record errors so that
one could discover what were the most common errors, and then modify
the parser to add error productions to cope with them.  It's the sort
of thing that could be added to year on year.


-- 
Jón Fairbairn [EMAIL PROTECTED]







Re: Question

1999-08-19 Thread Jon . Fairbairn

On 20 Aug, Bob Howard wrote:

>  data BTree Integer = Leaf Integer | Node Integer (BTree Integer) (BTree Integer)
  ^
  this ought to be a type variable name, but you've put the
  name of a type.

>  mkTree :: Integer -> BTree
  ^ argument missing
>  mkTree 0 = Leaf 0
>  mkTree int = Node int (mkTree (int - 1)) (mkTree (int -1))

Actually, I have fond memories of Algol compilers that gave error
messages pretty much as comprehensible as those above.  I guess the
problem is that Haskell compilers are prepared by people who have more
pressing tasks than repeating old work on user friendly error messages
:-(

  Jón

-- 
Jón Fairbairn [EMAIL PROTECTED]







Re: Haskell Wish list: library documentation

1999-09-08 Thread Jon . Fairbairn

On  8 Sep, George Russell wrote:
> Don't add more functions like concatSep to the standard library or prelude. 

Certainly not to the prelude, but I think there is a strong case for
evolving the standard library based on what people use.  I use
((concat .) intersperse) quite a lot, and having a standard name for
it would be a good thing.  concatWith would be another possible name.

> Instead document what is there better.

Both.

> (1) document the IO functions in one place

Hear hear. One might argue that the definitions ought to be in the
same module, too.  I'd prefer a structure where there was a prelude
that contained next to nothing (just the stuff that the language
itself depends on) and libraries, together with a 'standard library'
that includes the stuff from each of these libraries that are at
present in the prelude.  Most beginners programmes might have to start
with

> import UsualStuff

but that's a small price to pay.

> (2) document all functions with some text

hear hear.

> (3) there should be an index of all functions,

hear hear.

> (4) Haskell implementors should be encouraged to modify the library report by adding
> their own functions and comments directly into the main text.

I'd rather see:

(4) Haskell implementors should be encouraged to implement exactly the
library report and confine deviations to separate (well documented)
libraries.

  Jón

-- 
Jón Fairbairn [EMAIL PROTECTED]







Re: Haskell Wish list: library documentation

1999-09-09 Thread Jon . Fairbairn

On  9 Sep, George Russell wrote:
> Here is my revised version of the documentation.  
  my :-) (which incorporates some of the other suggestions.)
I've given reasons at the bottom.

Type:

> unzip :: [(a,b)] -> ([a],[b])

unzip takes a list of pairs and returns a pair of lists.

Definition:

> unzip l = (map fst l, map snd l)--  [1]

Description:

see zip;  unzip is such that if 
unzip l = (a, b)
  then  zip a b = l   --  [2]

Examples:

   unzip [(1, 4), (2, 5), (3, 6)] = ([1, 2, 3], [4, 5, 6])--  [3]

See Also: unzip3


Notes about the above:

[1] The prelude is supposed to give definitions that are semantically
correct but are not necessarily efficient (eg sort), and I think
this is clearer.  There are other definitions in the prelude that
could be made easier to understand.

[2] the motivation for the name comes from zip, and it makes it harder
to describe unzip when it's only necessarily true that zip undoes
what unzip does, and not vice versa.

[3] I think this example is slightly easier, though on second thoughts

unzip [('a', 1), ('b', 2), ('c', 3)] = (['a', 'b', 'c'], [1, 2, 3])

is better still.


Unrelated whinge:

I missed the discussion that decided that show should omit the
syntactically unnecessary spaces when converting lists and tuples.
While this may save space in files, I don't see that we are
equipped to break with centuries of typographic tradition wrt
spaces and commas.

-- 
Jón Fairbairn [EMAIL PROTECTED]








Re: Haskell Wish list: library documentation

1999-09-09 Thread Jon . Fairbairn

On  9 Sep, Christian Sievers wrote:
> It's a good idea to use two different types in an example, but Char
> is not well chosen, because the canonical way to write the above
> result is ("abc",[1,2,3]).

Good point.  String is best:

 unzip [("a", 1), ("b", 2), ("c", 3)] = (["a", "b", "c"], [1, 2, 3])


-- 
Jón Fairbairn [EMAIL PROTECTED]







Re: tuple component functions

1999-09-16 Thread Jon . Fairbairn

On 16 Sep, Keith Wansbrough wrote:
> I suggest calling them "pi13" or "prj13" rather than "tuple31", though.

pi1_3 or proj1_3 or select_1_3 or sel_1_3, even s_1_3 -- omitting the
"_" means sel is ambiguous (!).  We should choose a scheme that can
cope with such things even if they are unlikely.

I don't think pi_m_n looks right unless you replace pi with the greek
letter (UNICODE, anyone?).

-- 
Jón Fairbairn [EMAIL PROTECTED]







New mailing list (Was Re: Mailing lists down for a while, should be back up now)

1999-09-27 Thread Jon . Fairbairn

On 27 Sep, Manuel M. T. Chakravarty wrote:
>  Antti-Juhani Kaijanaho <[EMAIL PROTECTED]> wrote,
> > Please don't define lists by who'll use them.  Define them by the topic
> > of discussion.
>  
>  Good point.  `haskell-help' or some such is definitely
>  better. 

'haskell-questions'? Maybe this list ought to be renamed
'advanced-haskell' or 'haskell-design'?

Whatever we call it I'd subscribe and try to be helpful.

  Jón 
-- 
Jón Fairbairn [EMAIL PROTECTED]








Reverse composition

1999-10-08 Thread Jon . Fairbairn

Some time ago there was a discussion about what to call reverse
composition (I can't find it in the archive - needs a search option?)

Just now I thought of .~ from . for composition and ~ (tilde, but
commonly called twiddle) for twiddling the order about.

Maybe we could adopt that as normal usage?
-- 
Jón Fairbairn [EMAIL PROTECTED]










Re: [haskell] Reverse composition

1999-10-08 Thread Jon . Fairbairn

On  8 Oct, Christopher Jeris wrote:
>  Personal taste in infix operators seems to be another good argument for a
>  camlp4-style preprocessor for Haskell. 

Please no!  I want to be able to read other folks programmes and vice
versa.  The whole point of suggesting a particular glyph on this foram
is so that we can swallow our personal pride and use a common language.

> For instance I would like to use
>  'o' for composition (since anybody who uses 'o' for a variable gets what
>  they deserve!) but I guess that would make the lexer not so nice.

You could use `o` already.  f `o` g looks no worse to me than f >.> g
et al.

-- 
Jón Fairbairn [EMAIL PROTECTED]
18 Kimberley Road[EMAIL PROTECTED]
Cambridge CB4 1HH  +44 1223 570179 (pm only, please)







Re: Reverse composition

1999-10-08 Thread Jon . Fairbairn

On  8 Oct, Jonathan King wrote:
>  I think you might see the point.  (No pun back there, I promise...) I
>  understand where using "." to mean composition came from, and I know that
>  it's a long-standing tradition in at least the Haskell community, but I
>  don't think the visual correspondence of . to the typographic glyph
>  "raised open circle" is so close that you'd really like to explain why
>  you diverged from current usage so much as to choose "." to mean
>  "composition". 

Back in the early Haskell discussions we argued about various options,
but I think Richard Bird and Phil Wadler were insistent that, because
function composition is so important for functional programming, the
symbol used should be something with very low visual weight.  Nowadays
we might actually think of using ° (which would suggest º or § for the
reverse ;-).  Not to mention using · for composition...

Even though I disagreed with the use of . in the original case, I was
persuaded, and still think it ought to be a single
character. Unfortunately most of the other good candidates have been
used elsewhere.

-- 
Jón Fairbairn [EMAIL PROTECTED]
18 Kimberley Road[EMAIL PROTECTED]
Cambridge CB4 1HH  +44 1223 570179 (pm only, please)








Re: Reverse composition

1999-10-08 Thread Jon . Fairbairn

On  8 Oct, Joe English wrote:
>  [I wrote]:
> > Just now I thought of .~ from . for composition and ~ (tilde, but
> > commonly called twiddle) for twiddling the order about.

>  I've also seen  .|  and |.  used for this purpose (by
>  analogy with Unix pipes.)

>  John Hughes' Arrow library spells it ">>>",

Oh well, I thought it might be cute enough to solve the argument, but
obviously not...

>  Along the same lines, are there accepted conventional infix operators
>  for the functions with types:
>  
>   (a0 -> b0) -> (a1 -> b1) -> (a0,a1) -> (b0,b1)
>   (a  -> b0) -> (a  -> b1) -> a -> (b0,b1))
>  
>   (a0 -> b0) -> (a1 -> b1) -> Either a0 a1 -> Either b0 b1
>   (a0 -> b)  -> (a1 -> b)  -> Either a0 a1 -> b
>  
>  (the last one is called "either" in the standard Prelude).

These were on my list to think of names as well.  In ponder I had `
(like a raised comma) and >< (product of functions).

>  I personally like:
>  
>   (f <*> g) (x,y) = (f x, g y)
>   (f <&> g) x = (f x, g x)
>   (f <+> g) (Left x)  = Left (f x)
>   (f <+> g) (Right y) = Right (g y)
>   (f <|> g) (Left x)  = f x
>   (f <|> g) (Right y) = g y

I'd go along with those -- if for no other reason than you being first
to suggest them, and wishing for less argument. They look OK too.


-- 
Jón Fairbairn [EMAIL PROTECTED]
18 Kimberley Road[EMAIL PROTECTED]
Cambridge CB4 1HH  +44 1223 570179 (pm only, please)








Idiomatic Haskell extension library (Re: Reverse composition)

1999-10-09 Thread Jon . Fairbairn

On  9 Oct, Heribert Schuetz wrote:

[(f <| g) x = f (g x); (f |> g) x = g (f x)]

>"Use symmetric glyphs for commutative operations and asymmetric glyphs
>for non-commutative operations. Reflect glyphs for flipped operations."

That would make me happy.

>  which I would suggest as a general guideline.

and I'd go along with that.

>  Similarly, I would prefer a pair of reflected symbols for normal and
>  reversed function application, e.g., <$ and $>. (Yes, these are not 100%
>  reflected, but almost.)

and that.  For the record, my taste isn't particularly bothered by
multi-character symbols; what swayed me in the past was the argument
that it was a problem for other folk.


* * *

Anyway -- I'd like to suggest that we put a library containing
definitions of simple operators of general utility somewhere readily
accessible.  The precise choice of name for operator doesn't matter
(though I think a certain amount of discussion is worthwhile).  What
matters is that for common functions such as the ones we have been
discussing the Haskell community should in general use the same names.

I'd include composition, function products (as in Joe English's
message) and operations on boolean predicates:

> (f &&& g) x = f x && g x
> (f ||| g) x = f x || g x
> notF f x = not (f x)

(I'm not wedded to those names.)

Where do we put it?



-- 
Jón Fairbairn [EMAIL PROTECTED]








Re: type question

1999-01-17 Thread Jon Fairbairn

> 
> This is a distilled version of a problem that arose in a student's program:
> 
> > f :: a -> a
> > f x = g
> >where
> >g :: a
> >g = x
> 
> Reading file "[...]":
> Type checking
> ERROR "[...]" (line 5): Inferred type is not general enough
> *** Expression: g
> *** Expected type : a
> *** Inferred type : _2
> 

> Is there a simple explanation for this phenomenon?

The scope of the type variable in the first type declaration 
doesn't include the function definition, so the g :: a is 
saying that g has to have type all t. t.

Wasn't there once some discussion of the question of making 
variables in type declarations for functions range over the 
body?
-- 
Jón Fairbairn [EMAIL PROTECTED]
18 Kimberley Road[EMAIL PROTECTED]
Cambridge CB4 1HH  +44 1223 570179 (pm only, please)





Re: deleteBy type

1999-12-05 Thread Jon Fairbairn

> 
> Is not deleteBy :: (a->Bool) -> [a] -> [a]
> more natural for the library than
>deleteBy :: (a->a->Bool) -> a -> [a] -> [a]
> ?

I'd say so.  In general the prelude seems rather weak on 
functions to manipulate predicates.

  Jón
-- 
Jón Fairbairn [EMAIL PROTECTED]
18 Kimberley Road[EMAIL PROTECTED]
Cambridge CB4 1HH  +44 1223 570179 (pm only, please)





Re: fixing typos in Haskell-98

2000-01-24 Thread Jon Fairbairn

> > Take and drop
> > [..]
> > I can see three alternatives:
> > 
> > (A) Make them defined for any n.  If n < 0, do something reasonable:
> > take:   give empty list
> > drop:   give whole list
> >
> > (B) Make them defined for n > length xs, but fail for n < 0.
> >
> > (C) Status quo
> > 
> > PROPOSAL: Use alternative (A)
> 
> I vote for (B). 

Ditto, though I would say that the restriction is that the 
argument should be a natural number, and its simply a 
failing of the type system that it cannot express this.

-- 
Jón Fairbairn [EMAIL PROTECTED]
18 Kimberley Road[EMAIL PROTECTED]
Cambridge CB4 1HH  +44 1223 570179 (pm only, please)





Re: string to Integer

2000-04-07 Thread Jon Fairbairn

> Then, the question is why we write
>   result = function operand1 operand2
> instead of
>   operand1 operand2 function = result
> 
> I actually think the latter is cooler.  :)

I think there may be cultural influences about word order and/
or writing direction creeping in here :-)
-- 
Jón Fairbairn [EMAIL PROTECTED]
18 Kimberley Road[EMAIL PROTECTED]
Cambridge CB4 1HH+44 1223 570179 (after 14:00 only, please!)






Re: more detailed explanation about forall in Haskell

2000-05-17 Thread Jon Fairbairn


I'm reluctant to get involved in this discussion, cheifly
because it seems to me that Jan is attacking a position that
has quite a long history with (inter alia) the argument that
a different position has a longer history, which doesn't
strike me as terribly likely to lead to insight.

Also my present powers of concentration don't allow me to 
keep up with the argument, so I'll just drop in a couple of 
points and duck out again.

> [Lars asked]
> > What is a 'type' in your oppinion?

[Jan replied]

> I look at it as a set (either a variable set or a specific set). E.g. I look
> at Bool as a specific set which itself contains
> values  True , False that are not sets. Next I interpret   something  like f
> :: a -> Int  as a family (indexed by a) of functions of   " set"  a into set
> Int. [snippety]
> It is up to someone else to say if such
> an interpretation shall lead into misinterpretation.

Interpreting types as sets is not straightforward: try 

 "Types are not sets" by James H. Morris, JR. 
  in POPL 1973

as one pointer into this area.

> I think Haskell will not be attractive to mathematicians
> if types MUST be read as formula's . If that is the case I
> can only say that I find the term "functional programming"
> a bit strange.

I don't think anyone said that they must. They can be, and
one useful way of interpreting a type is as a statement of
limitations on the use and behaviour of a term.

f :: A -> B can be read as "if x is of type A, then f x will
be of type B"

x :: forall a . E can be read as "for all types A, x :: E [A/a]"

I think the major source of confusion is that Haskell
started out using the convention that a type expression
containing a free variable was understood as being
universally quantified at the top level (a convention which,
I might add, I argued against in the first Haskell
committee, so nyaa...), but then added 'forall' as an
extension later (I thought this was going to happen :-))

Apart from that, I think that (once they have had the
conventions and notation described to them) most
mathematicians are not going to be put off by the type
system. Certainly mathematicians must be warned against
interpreting types simply as sets, but they also need to be
warned that a "function" is not a function in the
mathematical sense either, being constrained by the limits
of computation.

> >
> > Isn't a type a statement about pre- and post-conditions, i.e. a formula?

I'd say that's another reasonable way of reading them.

> I can't answer this since I have never read the definition of a type in say
> typed lambda calculus.

Go on then! It won't hurt!

Cheers,
  Jón

-- 
Jón Fairbairn [EMAIL PROTECTED]
18 Kimberley Road[EMAIL PROTECTED]
Cambridge CB4 1HH+44 1223 570179 (after 14:00 only, please!)






Re: When is an occurrence an occurrence

2000-06-10 Thread Jon Fairbairn

> Me too, for (A)!  (B) looks too ugly for me.  A type declaration should
> refer to the "most local" definition of the name.

I go for A, though I'd say that type declarations are part 
of the definitions and the definitions in a module 
obviously are of names in that module.

> Btw, why would one declare the type of a function defined outside the
> current module?  For documentation only?  I would just use a comment if
> that's the case. 

You might want to restrict the type of an imported function 
to something less polymorphic.  But it seems to me that the 
logical place for such things is in the import list, since 
this is effectively defining the environment for the module.

   Jón

-- 
Jón Fairbairn [EMAIL PROTECTED]
18 Kimberley Road[EMAIL PROTECTED]
Cambridge CB4 1HH+44 1223 570179 (after 14:00 only, please!)






Re: Library conventions

2000-06-23 Thread Jon Fairbairn

Lennart Augustsson wrote:
> Frank Atanassow wrote:
> >   2) The Prelude doesn't use it.
> 
> Well, it doesn't for historical reasons.

Am I alone in thinking that the prelude is desperately in 
need of restructuring?  Has anyone got any proposals for 
nested modules (so we could have Prelude.List.head)?

> >   3) Nobody else uses it either, except me (and Chris, apparently :).
> 
> I do.  I think many people do. 

I would if I needed it.

> >   4) Qualified infix operators are ugly.
> 
> Yes, I can't deny that. :)

That seems like a presentation problem.  One day an editor 
might be persuaded to display Prelude.+ as (till ex.) + in 
proper size and 'Prelude' in smaller type beneath it or as 
a subscript.

 Jón

-- 
Jón Fairbairn [EMAIL PROTECTED]
18 Kimberley Road[EMAIL PROTECTED]
Cambridge CB4 1HH+44 1223 570179 (after 14:00 only, please!)






Re: Precision problem

2000-07-18 Thread Jon Fairbairn

> No, but they ARE, assuming IEEE arithmetic, 

which is what the Report says, isn't it.

> discrete mathematical objects with an arithmetic as well
> defined as that on the integers.  To do constant folding
> according to different rules is, IMHO, outrageous.

yes

> Surely this is obvious to Haskell programmers?

to me, anyway.  If two runs (with different flags) of the
compiler produce programmes that give different results,
then one of them isn't adhering to the standard, (and so
should be noted as such).

-- 
Jón Fairbairn [EMAIL PROTECTED]
18 Kimberley Road[EMAIL PROTECTED]
Cambridge CB4 1HH+44 1223 570179 (after 14:00 only, please!)






Re: Inferring types

2000-09-08 Thread Jon Fairbairn


> If you define `p' as a syntactic function, e.g.
> 
>   p x y = x + y
> or
> 
>   p x = (+) x
> 
> rather than via
> 
>   p = (+)
> 
> then the monomorphism restriction does not apply, and so the type inferred
> for `p' will be the correct polymorphic type `Num a => a -> a -> a'.

May I just take the opportunity to say that this is horrid?
-- 
Jón Fairbairn [EMAIL PROTECTED]
18 Kimberley Road[EMAIL PROTECTED]
Cambridge CB4 1HH+44 1223 570179 (after 14:00 only, please!)






Re: old easter egg

2000-12-01 Thread Jon Fairbairn

On Fri, 1 Dec 2000, Zhanyong Wan wrote:

> 
> Ronald Kuwawi wrote:
> > 
> > open text editor, type
> > hash :: [Char] -> Int
> > hash = (foldl (+) 0) . (map ord)

> hash "HASKELL%98"


hash "Haskell Ninety Eight !!" 

surely?
-- 
Jón Fairbairn [EMAIL PROTECTED]


___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: fixity for (\\)

2001-01-17 Thread Jon Fairbairn

On Wed, 17 Jan 2001, Koen Claessen wrote:
> I propose that it gets the following fixity:
> 
>   infixl 5 \\

Unless the it's common usage outside of Haskell, I oppose!

Getting 

   List> [1,2,3]\\[2]\\[3]
   ERROR: Ambiguous use of operator "(\\)" with "(\\)"

at compile time does no harm, but getting [1] instead of
[1,3] _at run time_ does do harm.
  Jón
-- 
Jón Fairbairn [EMAIL PROTECTED]
31  Chalmers Road[EMAIL PROTECTED]
Cambridge CB1 3SZ  +44 1223 570179 (pm only, please)


___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



RE: Combinator library gets software prize

2001-01-22 Thread Jon Fairbairn

On Sun, 21 Jan 2001, David Bakin wrote:

> This article is very good, and having read the conference paper earlier
> in the year I finished it with only one question:  What's a 'quant' ...
> and is it good or bad to be one?
> 
> "Ten years ago, Jean-Marc Eber, then a quant at Société
> Générale, ..."

The OED has:

  1. A pole for propelling a barge, esp. one with a cap at
the top and a prong at the bottom to
prevent it from sinking in mud. Also attrib., as quant-pole.

and

  2. In a windmill: 
  1924 Trans. Newcomen Soc. III. 42 All the framing and
gearing of these mills are of wood, the only important parts
of iron being the wrought iron gudgeons upon which the
shafts revolve, and perhaps the `quants' or spindles which
drove the runner stones.


So perhaps he was tall, thin and fond of wearing a cap?

 :-)

-- 
Jón Fairbairn [EMAIL PROTECTED]
31  Chalmers Road[EMAIL PROTECTED]
Cambridge CB1 3SZ  +44 1223 570179 (pm only, please)


___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: Anomalous Class Fundep Inference

2001-05-05 Thread Jon Fairbairn

Ashley Yakeley <[EMAIL PROTECTED]> wrote
> OK, I understand it a bit better now. This code does not compile:
> --
> class X a
> instance X Bool
> instance (Num a) => X a
> --
> Can someone explain why the two instances overlap, given that Bool is not 
> an instance of Num?
> 
> Would it be possible for Haskell to figure out this sort of thing and not 
> complain about it, or would that lead to nasty problems?

Think what would happen if someone had a module that did define
Bool as an instance of Num and imported the class X.

-- 
Jón Fairbairn [EMAIL PROTECTED]
31 Chalmers Road [EMAIL PROTECTED]
Cambridge CB1 3SZ+44 1223 570179 (after 14:00 only, please!)



___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: Notation question

2001-05-29 Thread Jon Fairbairn


> and not just type systems but also other aspects of operational
> semantics. What we have here is a single rule from a rule-based
> inductive definition of a certain relation G |- s :: S between typing
> environments G, expressions s and types S.

It's probably worth mentioning here that this notation
originated (I think) in mathematical logic, as a way of
presenting formal systems. Try "Gentzen", "Natural
Deduction" and "Sequent Calculus" as search terms.

  Jón




___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



foldl'

2001-07-28 Thread Jon Fairbairn

Unless I'm mistaken, foldl' (the strict version of foldl)
doesn't appear in (the export list of) the standard prelude
or the list library.

Is there a good reason for this? New users quite quickly
find that they need it.

 Jón


-- 
Jón Fairbairn [EMAIL PROTECTED]
31 Chalmers Road [EMAIL PROTECTED]
Cambridge CB1 3SZ+44 1223 570179 (after 14:00 only, please!)



___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: series

2001-08-15 Thread Jon Fairbairn

> >  hello, i just want to ask a simple question: does
> > somebody have or knowwhere to find a haskell program that
> > calculates the number e, that is the list of infinite
> > digits?

>   It's a nice problem, which I encountered many years
> ago as one of the first examples I saw of lazy evaluation!

Isn't it in one of David Turner's books?
-- 
Jón Fairbairn [EMAIL PROTECTED]
31 Chalmers Road [EMAIL PROTECTED]
Cambridge CB1 3SZ+44 1223 570179 (after 14:00 only, please!)



___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: Haskell 98 - Standard Prelude - Floating Class

2001-10-18 Thread Jon Fairbairn

> On Tuesday 16 October 2001 07:29, Fergus Henderson wrote:
> > [...]
> > The whole idea of letting you omit method definitions for methods with
> > no default and having calls to such methods be run-time errors is IMHO
> > exceedingly odd in a supposedly strongly typed language, and IMHO ought
> > to be reconsidered in the next major revision of Haskell.
> 
> This is exactly what I think.

I agree too, but being able to omit method definitions is
sometimes useful -- would it be possible to make calls to
those methods a /static/ error? I suspect this would be hard
to do.

-- 
Jón Fairbairn [EMAIL PROTECTED]
31 Chalmers Road [EMAIL PROTECTED]
Cambridge CB1 3SZ+44 1223 570179 (after 14:00 only, please!)



___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: Transmitting parameters

2001-11-02 Thread Jon Fairbairn

> At 2001-11-01 22:10, raul sierra alcocer wrote:
> 
> >What mechanism of transmiting parameters does Haskell implement?
> 
> By value.

Yes, though one might equally say that they are passed by
reference, since in

g = let f x = x+x
z = factorial 1000
 in f z * z

the 'first' instance of x forces z to be evaluated and
updated, the second instance of x uses this updated value,
and so does the final occurrence of z.

-- 
Jón Fairbairn [EMAIL PROTECTED]
31 Chalmers Road [EMAIL PROTECTED]
Cambridge CB1 3SZ+44 1223 570179 (after 14:00 only, please!)



___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: read-ing scientific notation

2001-10-14 Thread Jon Fairbairn

> > The lexical syntax says that
> > 10e3
> > means
> > 10 e3
> > (i.e. two lexemes).   I don't like this choice, and it could be "fixed"
> > in the Revised H98 report.
> 
> What is the likelihood of anyone *intentionally* writing an integer
> abutted directly with a varid, followed directly by another integer,
> and no intervening whitespace?  Nil, unless you are entering an
> obfuscated code contest, I reckon.  This looks like a good change
> to me.

Given that someone might well intend f 10 e3 and
accidentally write f 10e3, if there's a change at all I'd be
happier to make 10e3 erroneous. While that case is probably
going eventually to be caught by the type checker, it's
better to have mistakes pointed out as soon as possible.

I already intensely dislike the fact that f [1..10] mistyped
as f [1.10] can get through both syntax and type-checking,
so I'd vote against making the syntax more permissive unless
someone can prove that all the errors that get through as a
result are going to be caught some other way at compile
time.

  Jón


-- 
Jón Fairbairn [EMAIL PROTECTED]
31 Chalmers Road [EMAIL PROTECTED]
Cambridge CB1 3SZ+44 1223 570179 (after 14:00 only, please!)



___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: n+k patterns

2002-01-30 Thread Jon Fairbairn

> > I argued that (Num a, Ord a) makes most sense to me.
> > You argued that (Integral a) was a conscious choice (something I
> > don't remember but I'm sure you're right), and is the right one anyway.
> > 
> > I'd be interested to know what others think.  If there's any doubt,
> > we'll stay with Integral.
> 
> My view is that (n+k) patterns are evil, so it doesn't really matter
> what we decide.  :-)  No, seriously, I'm a little worried about
> widening the range of numeric types for which (n+k) patterns are
> supposed to work.  I can (just about) imagine wanting to use Rationals
> in an (n+k) pattern, but Float and Double? 

I dimly remember that the justification for having n+k was
to allow inductive definitions, which only applies to
Integral. I'd vote for keeping it as it is, too.

  Jón




___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: Why is this function type-correct

2002-03-04 Thread Jon Fairbairn

"Rijk J. C. van Haaften" <[EMAIL PROTECTED]>
wrote:
> Recently, I wrote a function similar to
> 
> x :: a
> x = x 42
> 
> which is type-correct (Hugs, Ghc, THIH).
> Still, from the expression it is clear
> that the type shoud have a function type.
> The definition
> 
> x :: a -> b
> x = x 42
> 
> is equally well accepted, though I can't
> see why this type would be correct. (I'd
> expect it to be too general.)
> 
> For what reasons are these types considered
> correct?

When you say

x :: a

you are asking that the compiler check that everything you
say about x is consistent with x being acceptable where
/any/ type is required.

In the application x 42, it requires that x be a function,
which is fine, because x has any type, and this includes
functions. When you say x = x 42, this requires that the
type returned from x 42 is the same as the type of x, again
fine because if x::a, then x:: Integer -> a also, so x 42:: a.

It works out in practise because x = x 42 gives x the value
bottom, and bottom::a for all a.
 

  Jón

-- 
Jón Fairbairn [EMAIL PROTECTED]
31 Chalmers Road [EMAIL PROTECTED]
Cambridge CB1 3SZ+44 1223 570179 (after 14:00 only, please!)


___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Standard Library report: List union

2002-03-04 Thread Jon Fairbairn

The current library report defines unionBy like this:

  unionBy eq xs ys =  xs ++ deleteFirstsBy eq (nubBy eq ys) xs

why does it take the nub of ys, but not xs?  I'd have expected

  unionBy eq xs ys =  (nubBy eq xs) ++ deleteFirstsBy eq (nubBy eq ys) xs

  Jón

-- 
Jón Fairbairn [EMAIL PROTECTED]
31 Chalmers Road [EMAIL PROTECTED]
Cambridge CB1 3SZ+44 1223 570179 (after 14:00 only, please!)


___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: Standard Library report: List union

2002-03-17 Thread Jon Fairbairn

> There's a remark at the beginning of 7.2 that says:
> 
> delete, (\\), union and intersect preserve the invariant=20
> that lists don't contain duplicates, provided that=20
> their first argument contains no duplicates.
> 
> The same applies to unionBy etc.   This design is one
> you might reasonably disagree with.  I'd have thought
> it would be more sensible to have the invariant that
> *both* arguments to union and intersect are assumed
> to be sets (no dups). 

That's partly what I was alluding to, but either way I'd
have thought that there were clearer definitions, for
example:


unionBy eq xs ys = xs ++ [y | y <- nubBy eq ys, not (any (eq y) xs)]



Jón

-- 
Jón Fairbairn [EMAIL PROTECTED]
31 Chalmers Road [EMAIL PROTECTED]
Cambridge CB1 3SZ+44 1223 570179 (after 14:00 only, please!)


___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: using less stack

2002-03-18 Thread Jon Fairbairn

> Apologies for the typo: that should have been 5 elements, not 500.
> 
> Amanda Clare wrote:
> > I have stack problems: my program uses too much stack. I suspect, from 
> > removing bits of code, that it's due to a foldr in my program. If I use 
> > foldr or foldl on a long list (eg >500 bulky elements for a 3M stack), 
> > is this likely to be filling the stack?

The fold itself won't be filling the stack. Without seeing
some of the code it's hard to tell, but the most common
cause of this sort of problem is a lack of strictness.

foldr (+) 0 [0..5000]

doesn't use up stack for the fold, but it builds a
suspension for all 5000 additions, and evaluating that
/does/ use stack unless the compiler has spotted that (+) is
strict. (What compiler/interpreter are you using?)

> > What is it that gets stored on 
> > the stack? If so, is there an obvious refactoring of the fold to use?

The solution is to stick in $! judiciously and use foldr'
(which seems to have got dropped from the standard libraries
at some point, so you'll have to write your own) that uses
$!.

  Jón


-- 
Jón Fairbairn [EMAIL PROTECTED]
31 Chalmers Road [EMAIL PROTECTED]
Cambridge CB1 3SZ+44 1223 570179 (after 14:00 only, please!)


___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: finding ....

2002-03-20 Thread Jon Fairbairn

> Could someone post an example of the creation of a
> temporary file where race conditions are important?

/any/ programme that does this on a multi-process system.

Between the test for existence and the creation, some other
process could have created a file of the same name. Then
the create fails because of insufficient permissions,
so the programme has to deal with failure anyway, or it
succeeds and stomps on the data belonging to the other
process.



do possible_handle <- try $ openFile "whatever" ReadMode
   case possible_handle 
 of (Right handle) -> do_things_to handle
(Left error) -> do whatever you would have done had
   the existence test returned false

is no more complex than a version using an existence test,
but to create a file for writing, surely we need an
openNewFile primitive? Otherwise we might open on a file
that already exists and hit the "stomp" error mentioned
above.


 Jón

-- 
Jón Fairbairn [EMAIL PROTECTED]
31 Chalmers Road [EMAIL PROTECTED]
Cambridge CB1 3SZ+44 1223 570179 (after 14:00 only, please!)


___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: using less stack

2002-03-20 Thread Jon Fairbairn

> Thanks for all the advice. In the end, I couldn't make $! work for me 
> (it always seems to be harder than I think it will be to use it, and $! 
> and deepSeq makes my code run slowly). 

:-(

> But a continuation passing style foldl worked wonderfully.

As Jay Cox pointed out by email, my answer was rot because I
had confused foldl and foldr

> I now have:
> 
>  > cpsfold f a [] = a
>  > cpsfold f a (x:xs) = f x a (\y -> cpsfold f y xs)
> 
> and f takes a continuation, Bob's my uncle, and I have a program that 
> runs quickly in constant space!

Good.  I'm curious to know from other readers whether
continuations like this are the only way of solving it,
though.

  Jón


-- 
Jón Fairbairn [EMAIL PROTECTED]
31 Chalmers Road [EMAIL PROTECTED]
Cambridge CB1 3SZ+44 1223 570179 (after 14:00 only, please!)


___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: finding ....

2002-03-20 Thread Jon Fairbairn

> On Wed, Mar 20, 2002, Jon Fairbairn wrote:
> > > Could someone post an example of the creation of a
> > > temporary file where race conditions are important?
> > 
> > /any/ programme that does this on a multi-process system.
> 
> Occasionally, the presence or absence of a file (usually empty) of a
> certain name in a certain directory is used for communication between
> processes on a multi-process system.

Hence the need for an atomic openNewFile.
-- 
Jón Fairbairn [EMAIL PROTECTED]
31 Chalmers Road [EMAIL PROTECTED]
Cambridge CB1 3SZ+44 1223 570179 (after 14:00 only, please!)


___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: ">>" and "do" notation

2002-03-29 Thread Jon Fairbairn

Wolfgang Jeltsch <[EMAIL PROTECTED]> wrote:
> It shouldn't be syntactic suger but at most an operator which does not belong
> to the monad class. One could define (>>) just as an ordinary function
> instead of a class member.

That sounds to me like the best idea so far. 

If (as a human reader of a programme) I see

do a <- thing1
   

and I notice (perhaps after some modifications) that a is
not present in , then I /really/ don't want a
change to

do thing1
   

to change the meaning of the programme.


  Jón


___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: ">>" and "do" notation

2002-04-02 Thread Jon Fairbairn

On Tue, 2 Apr 2002 10:00:37 +0200 (MET DST), John Hughes
<[EMAIL PROTECTED]> wrote:
>   >If (as a human reader of a programme) I see
>   >
>   >do a <- thing1
>   >   
>   >
>   >and I notice (perhaps after some modifications) that a is
>   >not present in , then I /really/ don't want a
>   >change to
>   >
>   >do thing1
>   >   
>   >
>   >to change the meaning of the programme.

> I think the point that's being missed in this discussion
> is that a monad is a n *abstract* type, and sometimes the
> natural "equality" on the abstract type is not the same as
> equality on representations. Of course, we want the left
> and right hand sides of the monad laws to have the same
> "meaning", and we want >> to "mean" >>= \_ ->, but this
> meaning is really up to the abstract equality, not the
> concrete one. If we can give >> a more efficient
> implementation, whic h constructs a better representation
> than >>= does, that's fine, as long as the two
> representations "mean" the same thing.

Point taken, but I remain unconvinced. What comes out of the
monad /isn't/ abstract; there's nothing to ensure that
subsequent use respects the abstraction.

> To be specific, the application that kicked off this
> discussion was program generation. In this example, it's
> not important that >> and >>= generate the same *program
> text*, the important thing is that they generate
> equivalent programs. If >> can more easily generate a more
> efficient program, that's fine.

Is it fine though?  Since it will be possible to inspect the
generated code, it's possible that a change from do {_ <- A;
B} to do {A; B} can radically alter the subsequent behaviour
of the programme.

> There's another example in QuickCheck, where we use a
> monad Gen for random value generation -- Gen a is a
> generator for random values of type a. Gen doe s not
> satisfy the monad laws: for example, g and g >>= return
> will usually generate different values. But viewed as
> *probability distributions* (which i s how we think of
> them), they are the same. "Morally", Gen is a monad.

Well, aren't there cases where generating the /same/
pseudo-random sequences is important? In such a case, making
what looks like a semantically neutral change to the
programme might invalidate years of stored results.

> This is all perfectly respectable, and has to do with the
> fact that Haskell i s a programming language, not
> mathematics -- so we represent equivalence classe s by
> values chosen from them. For the *language* to rule out
> constructing different representations for "equivalent"
> constructions, such as >> and >>=, would be unreasonable.

Here's the problem. Your argument sounds very similar to the
one against type checking. That /you/ can get it right
doesn't encourage me to believe that J Random Hacker isn't
going to abuse the facility. It's not as if you couldn't
define >!= and >! for something that's nearly a monad, it
would just stop you using the do notation, which is, I think
fair, since Haskell provides no way of selecting the correct
form of equality for do {_ <- A; B} == do {A; B}.

  Jón


-- 
Jón Fairbairn [EMAIL PROTECTED]
31 Chalmers Road [EMAIL PROTECTED]
Cambridge CB1 3SZ+44 1223 570179 (after 14:00 only, please!)


___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: Dependent Types

2002-05-16 Thread Jon Fairbairn

"Dominic Steinitz" <[EMAIL PROTECTED]> wrote:
> I've managed to crack something that always annoyed me when I used to do
> network programming.
[. . .]
> 
> Suppose I want to send an ICMP packet. The first byte is the type and the
> second byte is the code. Furthermore, the code depends on the type. Now you
> know at compile time that you can't use codes for one type with a different
> type. However, in Pascal (which is what I used to use) you only seemed to
> be
> able to carry out run time checks.

I'm not sure I understand your problem.  I don't see what's
wrong with the following approach, which is Haskell 98. The
type byte is coded as the type of the packet. Excuse the
perhaps ideosyncratic style ... (in particular, I'm
expecting people to use import qualified with this).


   module ICMP where

   data Type = Redirect RedirectData
 | TimeExceeded TimeData

   {- so you get an alternative for each of the packet types -}

   instance Enum Type where
fromEnum (Redirect _) = 5
fromEnum (TimeExceeded _) = 11

   {- we can't derive Enum for ICMP.Type, because it has non-nullary
  constructors. That just makes it a bit more tedious
  One could provide a class "code" with code:: t -> Int
  instead of fromEnum
-}

   {- now we define individual record types for each of the different
  ICMP types -}

   data RedirectData = RedirectData {redirectCode:: RedirectCode,
 ip_addr:: Int, -- whatever
 redirectData:: [Int]} -- or whatever

   data RedirectCode = RedirNet
 | RedirHost
 | RedirNetToS
 | RedirHostToS
deriving Enum

   data TimeData = TimeData {timeCode:: TimeExceededCode,
 timeData:: [Int]} -- or whatever

   data TimeExceededCode = ExcTTL
 | ExcFragTime
deriving Enum

   {- Since Haskell 98 doesn't have MPTCs, if we want to
  encode packets as anything other than [Int] we'd have
  to define more classes.  Encode serves as an example. -}
 
   class Encode t where
 encode:: t -> [Int]

   instance Encode Type where
encode p@(Redirect d) = fromEnum p: encode d
encode p@(TimeExceeded d) = fromEnum p: encode d

   instance Encode RedirectData where
encode d = fromEnum (redirectCode d): ip_addr d: redirectData d

   instance Encode TimeData where
encode d = fromEnum (timeCode d): 0: timeData d



so one can go 

   encode (Redirect (RedirectData RedirNet 0 [0]))

and get [5,0,0,0], but 


   encode (TimeExceeded (TimeData RedirNet 0 [0]))

gives an error, as one would hope. What am I missing?


Cheers,

  Jón
-- 
Jón Fairbairn [EMAIL PROTECTED]
31 Chalmers Road [EMAIL PROTECTED]
Cambridge CB1 3SZ+44 1223 570179 (after 14:00 only, please!)


___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



fold on Monad?

2002-05-29 Thread Jon Fairbairn


Suppose I have a task I want to do to each line of a file,
accumulate a result and output it, I can write

   main = do stuff <- getContents
 print $ foldl process_line initial_value (lines stuff)

ie, it's obviously a fold

I can't see a way of doing the same thing directly on the
IO: I'd like to write something similar to

   main = do res <- foldX process_line initial_value getLine
 print res

foldM almost does it:

   main = do res <- foldM process initial_value (repeat getLine)
 print res

   process a g
= do line <- g
 return (process_line a line)

but that goes on forever (or some fixed amount if (replicate n/repeat))

I feel this ought to be straightforward -- the structure is
obviously some sort of fold, but I shouldn't have to use a
list -- so I must be missing something obvious. What is it?

  Jón

-- 
Jón Fairbairn [EMAIL PROTECTED]
31 Chalmers Road [EMAIL PROTECTED]
Cambridge CB1 3SZ+44 1223 570179 (after 14:00 only, please!)


___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



IO and fold (was Re: fold on Monad? )

2002-05-29 Thread Jon Fairbairn

> foldr, foldM, etc. derive a recursive computation from the
> recursive structure of an input list, so you have to feed
> one in. If you want to bypass the list, you could use
> IO-observations (getLine, isEOF) instead of list
> observations (head/tail, null):


Yes you can define it, I should have been a bit more direct.
It seems to me that there's something odd about the way the
IO monad interacts with bulk operations on files.  In
particular, it seems odd that getContents should ever be the
easiest way of tackling something, rather than some natural
operation on Monads. Doing something to each line of a file
is such a common kind of computation that it ought to be
easy!

It also seems wrong that end of file should be an exception
-- after all, for most files other than a terminal or
"special file", having an end is the norm. As a result, the
definition you gave strikes me as awkward (no fault of
yours!). It suggests to me that a Monad isn't quite enough.

One of the great things about fold is that you don't have to
code the test for the end: it's encapsulated in the
higher-order function. Shouldn't there be the same for IO?

> Whether that is a real fold, or what the real fold/unfold would
> look like, I leave to others;-)

I suppose that was part of my real question, aimed at the
others who've got the mental processing power to answer such
things.

Cheers,
  Jón
-- 
Jón Fairbairn [EMAIL PROTECTED]
31 Chalmers Road [EMAIL PROTECTED]
Cambridge CB1 3SZ+44 1223 570179 (after 14:00 only, please!)


___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



layout rule infelicity

2002-05-30 Thread Jon Fairbairn


Two very similar programmmes:

> possible_int = do skip_blanks
>   fmap Just int
>+++ (literal "-" `as` Nothing)

> possible_int = do skip_blanks
>   fmap Just int
>   +++ (literal "-" `as` Nothing)


I think this is extremely bad language design! In general I
like having layout rules, but I've often thought that they
ought to take note of expressions, not just things in {...}
and that there ought to be "dead zones" where no programme
text is allowed, so that everything starting with the second
example and ending with

> possible_int = do skip_blanks
>   fmap Just int
> +++ (literal "-" `as` Nothing)

should be rejected.

This example clinches it for me.  Can anyone more au fait
with the layout rule figure out how to do it?

(My past irritation was that
  ... if p
  then q
  else r

is acceptable in some circumstances, but one has to use

  ... if p
 then q
 else r

in others. Having programmes rejected I don't mind, but
having them accepted when they are too close to right but
still wrong, I really do mind)

-- 
Jón Fairbairn [EMAIL PROTECTED]


___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: [Fwd: F#]

2002-05-30 Thread Jon Fairbairn

> Hey Simon et al at Micro$oft, when will there be an H#?

But H# is C! we don't want that, surely? :-)

  Jón

-- 
Jón Fairbairn [EMAIL PROTECTED]
31 Chalmers Road [EMAIL PROTECTED]
Cambridge CB1 3SZ+44 1223 570179 (after 14:00 only, please!)


___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: layout rule infelicity

2002-05-30 Thread Jon Fairbairn

> I like layout but I think the existing rules are too
> complicated.  Unfortunat ely it's difficult to do anything
> with them without breaking vast swathes of existing code,
> so we'll just have to put up with them.

Well, there's two things to consider: Haskell 98, which
probably shouldn't change, and extended Haskell, which
probably should. Especially if we can make the rules both
simpler and better.

> The reason I think layout is better than using {'s and ,'s is that humans
> use the layout to group the structure anyway, which means you can have 
> confusing situations where a structure looks alright to a human but not
> to a computer.

Which is exactly the problem with the programme I
posted. Having thought about it a bit, it strikes me that
the particular problem is the insertion of a closing brace.
From the human reader's point of view, there's no visual
equivalent of the closing brace in the example:

> possible_int = do skip_blanks
>   fmap Just int
>   +++ (literal "-" `as` Nothing)

What happens is that a semicolon is inserted because the
indentation is the same as the previous line -- that's fair
enough, subject to some quibbles about treating all
expressions the same -- but then the +++ is a syntax error
unless a closing brace is inserted.

Visually, the equivalent of a closing brace is when
indentation is less (to my eye it ought to be right down to
where the 'do' is and inbetween be an error).  What's wrong
with the notion that closing braces should only be inserted
when the indentation is less (or the file ends)? This would
reject some programmes, but only ones where the appearance
is misleading.

So 

> possible_int = do skip_blanks
>   fmap Just int
>+++ (literal "-" `as` Nothing)

> whatever ...

parses as 


> possible_int = do {skip_blanks
>   ;fmap Just int
> +++ (literal "-" `as` Nothing)

>   }
> whatever ...

and

> possible_int = do skip_blanks
>   fmap Just int
>   +++ (literal "-" `as` Nothing)

> whatever ...

parses as 

> possible_int = do {skip_blanks
>   ;fmap Just int
>   ;+++ (literal "-" `as` Nothing)

>   }
> whatever ...

and then gives a syntax error

but 

> possible_int = do skip_blanks
>   fmap Just int
>  +++ (literal "-" `as` Nothing)

> whatever ...

parses as 

> possible_int = do {skip_blanks
>   ;fmap Just int
>   }
>  +++ (literal "-" `as` Nothing)

> whatever ...

Which is just about acceptable to me, because the +++ does
stick out, though I'd prefer that one to be rejected too.

I wasn't fit enough to follow the earlier discussions of the
layout rule, so I'm not sure how this interacts with
previous awkward cases.  I'd be happiest if we could come up
with a rule that didn't involve sticking in braces and
semicolons because it won't parse otherwise. Can someone
remind me why the "A close brace is also inserted whenever
the syntactic category containing the layout list ends" part
of the rule is there?

  Jón


-- 
Jón Fairbairn [EMAIL PROTECTED]
31 Chalmers Road [EMAIL PROTECTED]
Cambridge CB1 3SZ+44 1223 570179 (after 14:00 only, please!)


___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: IO and fold (was Re: fold on Monad? )

2002-05-30 Thread Jon Fairbairn

> >Yes you can define it, 
> 
> And you can, as well.

Man sollte sich nicht darauf verlassen, daß ein Englander
"man" verwendet, wenn es angebraucht wäre¹.

> That's how common idioms come into being;
> there's no special magic about the folds already in existence.

Well, my point is that there is -- indeed some ways of
defining the type for lists use a fold as the starting
point. I mentioned the lack here because I think there is
some deeper structure that someone cleverer than me may be
able to see.

> 
> >It seems to me that there's something odd about the way the
> >IO monad interacts with bulk operations on files.  
> 
> That may be more related to IO than to the monadic approach
> to it 

Yes. Hence the change of subject line. 

> >In particular, it seems odd that getContents should ever be the
> >easiest way of tackling something, 
> 
> Who says that?

I did! I think getContents is a klugey hangover from stream
based I/O, and the existence of "semi-closed handles"
supports that, so I'm hoping that people might become
interested in looking at the question.

> >One of the great things about fold is that you don't have to
> >code the test for the end: it's encapsulated in the
> >higher-order function. Shouldn't there be the same for IO?
> 
> Isn't it?
> 
> getContents = foldX (++) "" -- we drop the newlines here..
> getLines = foldX (:) []
> 
> No eof-testing in sight.

Sure, once we've defined foldX, but then we need to know
whether it really is a fold &c.  I should remember to make
my messages to the list less indirect.

> So we've mostly got a fold lifted into the io-monad, with getLine
> delivering the "head" (and implicitly truncating further input to
> the "tail"). What more do you want?-)

Theory! That's what I want!

Cheers,

   Jón

1. I had to get help with this; perhaps it would have been
better to leave my numerous mistakes in it!

-- 
Jón Fairbairn [EMAIL PROTECTED]
31 Chalmers Road [EMAIL PROTECTED]
Cambridge CB1 3SZ+44 1223 570179 (after 14:00 only, please!)


___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: layout rule infelicity

2002-05-30 Thread Jon Fairbairn


I wrote:
> > Can someone remind me why the "A close brace is also inserted whenever
> > the syntactic category containing the layout list ends" part
> > of the rule is there?

Lennart wrote:
> It's so you can write
> let x = 2+2 in x*x
>  (and similar things)

and Arjan van IJzendoorn wrote:
> x = (3, case True of 
>  True -> 4)
> 
> The ')' ends the syntactic category 'tuple'

So we get all this misery just so that people can cram
things onto fewer lines?

> let x = 2+2 in x*x

could be

> let {x = 2+2} in x*x

or

> let x = 2+2
>  in x*x

and 
> x = (3, case True of 
>  True -> 4
> )

would be fine.

I'd like to see a "-fuse-simpler-layout-rule"¹ option on the
compilers. . .


  Jón

1. Why "-f" anyway? It took me ages to work out what
"-fallow-overlapping-instances" meant -- I wondered how
"fallow" could apply to overlapping instances.


-- 
Jón Fairbairn [EMAIL PROTECTED]
31 Chalmers Road [EMAIL PROTECTED]
Cambridge CB1 3SZ+44 1223 570179 (after 14:00 only, please!)


___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: FW: Haskell accumulator

2002-06-14 Thread Jon Fairbairn

> Paul Graham is collecting canonical accumulator generators at
> http://www.paulgraham.com/accgen.html , and has Dylan, E, JavaScript,
> various dialects Lisp, Lua, Rebol, Ruby, Perl, Python and Smalltalk.

As others have implied, the only correct answer to this is
"it's the wrong question".  One of the major advantages of
functional programming is that you do most things without
global variables, because they are a Bad Thing. So an
accumulator based on a variable is simply not the
appropriate abstraction in most cases.

Think about sum:

sum = foldl (+) 0

That works by using an accumulator, but Haskell is so
expressive you don't even need to mention the fact!

In addition the question is underspecified -- what happens,
for example if the argument isn't a number? This is not a
problem for Haskell, of course, but in allowing the lisp
version to throw an exeption he finesses away the advantage
of strong typing.

> Could the serious Haskellers comment on this attempt of mine?
> 
> foo n = do
>   n' <- newIORef n
>   return (\i -> do { modifyIORef n' (i+); readIORef n' })


What strikes me about this, though, is that perhaps the
imperative primitives in Haskell aren't quite perfectly
designed. It seems to me that modifyIORef ought to return
either the IORef of its value. In Algol68 if n IS a REF INT,
(n +:= i) has the value a (which will now contain it's
previous contents plus i), so it's a time honoured form.

If we had such a version (call it modIORef) we could dazzle
the blighters with:

foo n = fmap (\n' i -> modIORef n' (+i) >>= readIORef)
 $ newIORef n

and if we had one that returned the value (say modReadIORef)

foo n = fmap (\n' i -> modReadIORef n' (+i)) 
 $ newIORef n

Now, it was the work of moments to define and test (helped
by the type system) the above new functions, which shows
what expressive power is really about.

 Jón

PS It's perhaps a bit disappointing that one needs a type
signature to use

foo = fmap (\n' i->modReadIORef n'(+i)) . newIORef

-- 
Jón Fairbairn [EMAIL PROTECTED]


___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: Library report, monad zero laws

2002-06-21 Thread Jon Fairbairn

> On Fri, Jun 21, 2002 at 12:50:21PM +0100, Simon Peyton-Jones wrote:
> > | From: Jon Fairbairn [mailto:[EMAIL PROTECTED]] 
> > | Sent: 20 June 2002 16:27
> > | To: Simon Peyton-Jones
> > | Subject: Library report, monad zero laws
> > | 
> > | The old report used to include 
> > | 
> > |  m >> zero = zero
> > |  zero >>= m = zero
> > |  m ++ zero = m
> > |  zero ++ m = m
> > | 
> > | after the other monad laws. Now mzero and mplus are in the 
> > | library, shouldn't there be some mention of these laws there? 
> > |  I'd be particularly keen to see a remark about 
> > | 
> > |  _|_ >> zero 
> > | 
> > | inevitably being _|_
> 
> Would you put that next to m >> zero = zero ?

Well, that's rather the point. At the moment the library
report just says "The class methods mzero and mplus are the
zero and plus of the monad.", which implies m >> zero =
zero, but it can't be.

-- 
Jón Fairbairn [EMAIL PROTECTED]
31 Chalmers Road [EMAIL PROTECTED]
Cambridge CB1 3SZ+44 1223 570179 (after 14:00 only, please!)


___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: Library report, monad zero laws

2002-06-21 Thread Jon Fairbairn


Apologies for responding to messages in reverse order . . .

> * My reluctance to change the draft H98 report is rising sharply.

Understood!

> * I don't think the H98 report has ever had laws about mzero etc.

No, they went on the transition from 1.4, I think.

> * And the whole laws business is flaky because people can and do
>make instances of Monad that don't obey the laws.

That's what made me ask the question. Either it shouldn't
say what it does about mzero being the zero, or it should
explain more.

So an alternative would be to remove the remark about the
zero, but then we'd be left with no clues about the
intentions. 

  Jón


-- 
Jón Fairbairn [EMAIL PROTECTED]
31 Chalmers Road [EMAIL PROTECTED]
Cambridge CB1 3SZ+44 1223 570179 (after 14:00 only, please!)


___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: Overloading and Literal Numerics

2002-06-27 Thread Jon Fairbairn

> Hi,
> I am trying to create an overloaded function "à la Java" to be able to
> call it either with a string or a number.
> Ex :
> definePort "http"
> definePort 80
> but I have problem with restrictions in Haskell's type system

> Is there a better solution ?

If we knew /why/ you wanted to do this we might be able to
help.  I can't see why you want to allow Strings, which have
far too wide a range of values, as arguments to something
that takes a port designator as an argument.

data Port = Tcpmux | Nbp | Echo_ddp | Rje | Zip | Echo_tcp | ...
 deriving Enum, ...

instance Num Port where ...

would seem like a better way to me.

  Jón

-- 
Jón Fairbairn [EMAIL PROTECTED]
31 Chalmers Road [EMAIL PROTECTED]
Cambridge CB1 3SZ+44 1223 570179 (after 14:00 only, please!)


___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: Overloading and Literal Numerics

2002-06-27 Thread Jon Fairbairn

> Jon Fairbairn <[EMAIL PROTECTED]> writes:
> 
> > data Port = Tcpmux | Nbp | Echo_ddp | Rje | Zip | Echo_tcp | ...
> >  deriving Enum, ...
> > instance Num Port where ...
> 
> Or, alternatively, just use Strings, and have a portFromString first
> check /etc/services for a match, then try to parse the string as a
> positive integer, and finally generate an error if no valid port can
> be determined?

Possibly, if there's really no way of making sure the error
happens at compile time.

-- 
Jón Fairbairn [EMAIL PROTECTED]
31 Chalmers Road [EMAIL PROTECTED]
Cambridge CB1 3SZ+44 1223 570179 (after 14:00 only, please!)


___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: Overloading and Literal Numerics

2002-06-27 Thread Jon Fairbairn

> Alain Cremieux wrote:
> I am trying to build a functional firewall generator. The first part
> describes the available protections (kernel, anti-address spoofing, etc.).
> The second desribes every protocol, and the necessary rules if the
> corresponding service is enabled (e.g. open the http port...). In the third
> one, the user will choose the services he wants to use/open and the static
> parameters (for instance the squid port number).
> I wanted the user part to be "user-friendly", even if it is an Haskell
> program. So the commands
> definePort "squidPort" 3128
> Seemed more logical than
> definePort "squidPort" "3128"
> 
> The problem is that the numeric literal 3128 is considered as being a member
> of Num class, and not as beeing an Int.
> So I can't write a unique function which accepts 1) the string "3128" 2) the
> literal numeric 3128   3) the string "3128:3129"(if the user wants to give a
> port range, for instance)

I understand the problem, but I still don't see why you want
strings here. [Int] would do. They'd just have to type
[3218..3130] for a range of port numbers, and you can define
ordinary variables:

   type Port = [Int]
   http:: Port
   http = [80]

You'd have to have them type

definePort "squidPort" [3128]

and that allows giving a range of ports where only one port
is required, but at least they are going to be constrained
to be numbers. With this, portRange [3128.3129] will give a
compile time error, where portRange "3128.3129" would have
to be a run-time error.

 Jón


-- 
Jón Fairbairn [EMAIL PROTECTED]
31 Chalmers Road [EMAIL PROTECTED]
Cambridge CB1 3SZ+44 1223 570179 (after 14:00 only, please!)


___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: class Function ?

2002-10-29 Thread Jon Fairbairn
On 2002-10-29 at 03:21PST Ashley Yakeley wrote:
> At 2002-10-29 02:43, Josef Svenningsson wrote:
> 
> >> I'm pretty sure it's not possible...
> >>
> >You mean in H98? Sure no! What I meant was to implement overloading of
> >function application as an extension of H98.
> 
> See my earlier message. If function application is overloadable, then 
> there must be some operator "funapp" that corresponds to it. But 
> operators themselves need function application, 
> so you end up with:
> 
> f a 
>  reduces to
> funapp f a
>  reduces to
> funapp (funapp (funapp f)) a
>  reduces to
> etc.

But we could just make $ the primitive instead of
juxtaposition (and infix the primary form).

Then f a is shorthand for f $ a and it stops there.

-- 
Jón Fairbairn [EMAIL PROTECTED]
31 Chalmers Road [EMAIL PROTECTED]
Cambridge CB1 3SZ+44 1223 570179 (after 14:00 only, please!)


___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: class Function ?

2002-10-29 Thread Jon Fairbairn
On 2002-10-29 at 04:09PST Ashley Yakeley wrote:
> At 2002-10-29 03:42, Jon Fairbairn wrote:
> 
> >But we could just make $ the primitive instead of
> >juxtaposition (and infix the primary form).
> >
> >Then f a is shorthand for f $ a and it stops there.
> 
> But then how would you overload $?

The class Function and it's first instance would have to be
built in (not too onerous since function application is
anyway). Not that I'm necessarily in favour of this, you
understand.

-- 
Jón Fairbairn [EMAIL PROTECTED]
31 Chalmers Road [EMAIL PROTECTED]
Cambridge CB1 3SZ+44 1223 570179 (after 14:00 only, please!)


___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: forall quantifier

2003-06-06 Thread Jon Fairbairn
On 2003-06-06 at 08:15BST "Simon Peyton-Jones" wrote:
> 
> I forget whether I've aired this on the list, but I'm
> seriously thinking that we should change 'forall' to
> 'exists' in existential data constructors like this one.

You did mention it, and there were several replies. I'd
characterise them as mainly falling into two classes: "Yes,
the change is sensible" and "No, it's all right as it is so
long as you stand on your head when reading programmes".

It doesn't seem so difficult to me. It's a matter of
thinking in terms of expressions for types and functions
that return types.

If you define

  type F a = forall t . (a, t)

and subsequently write 

  e:: F Int

this is equivalent to writing

  e:: forall t . (Int, t)


Now, although we don't have type expressions that correspond
to the RHSs of data declarations, it seems perfectly
reasonable to expect things to work as if we did -- the
chief problem being that we can't see from the context which
constructors are data and which type. So

  data D a = forall t . MkD a t

leads us to interpret

  e:: D Int

as

  e:: forall t . MkD a t

I don't think that the problem of type and constructor
namespaces detracts from this argument -- if anything, it
points up a problem with data constructors, not quantifiers.

>From there it's easy to decide that to get an existential
type we need to write

  data D a = exists t . MkD a t

(and type F a = exists t . (a, t) looks quite reasonable
too).

 
> One has to explain 'forall' every time.  But we'd lose a
> keyword.

Seems like a small price to pay. As Christian Maeder points
out it is a loss only in the type variable namespace.

As to omitting the quantifier, I say no, since the omission
of quantifiers elsewhere corresponds uniformly to universal
quantification.

 Jón

PS that's one heck of an email address you have there, 
Simon!
-- 
Jón Fairbairn [EMAIL PROTECTED]
31 Chalmers Road [EMAIL PROTECTED]
Cambridge CB1 3SZ+44 1223 570179 (after 14:00 only, please!)


___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: for all quantifier

2003-06-09 Thread Jon Fairbairn
On 2003-06-08 at 18:03PDT Ashley Yakeley wrote:
> In article <[EMAIL PROTECTED]>,
>  [EMAIL PROTECTED] (Peter G. Hancock) wrote:
> > Thanks!  It made me wonder what colour the sky is on planet Haskell. 
> > From a Curry-Howard point of view, (I think) the quantifiers are 
> > currently the wrong way round.  It is actually painful! 
> 
> Well don't forget the other one:
> 
> data MyType1 = forall a. MkMyType1 a;
> 
> data MyType2 = MkMyType2 (forall a. a);
> 
> You can put anything in a MyType1, but only something of type (forall a. 
> a) such as "undefined" in a MyType2.

I'm not sure I understand your implication. After the
proposed change you'd have to write:

> data MyType1 = exists a. MkMyType1 a;
> 
> data MyType2 = MkMyType2 (forall a. a);

to get the same effect, and we'd have that

> data MyType1a = MkMyType1a (exists a . a)

would be (bar alpha) equivalent to MyType1, and (after a
suitable grace period)

> data MyType2a = forall a . MkMyType2a a

would be like MyType2, which all seems much more reasonable
than the present notation.


-- 
Jón Fairbairn [EMAIL PROTECTED]
31 Chalmers Road [EMAIL PROTECTED]
Cambridge CB1 3SZ+44 1223 570179 (after 14:00 only, please!)


___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


  1   2   >