Re: Isn't this tail recursive?

2002-03-12 Thread Bjorn Lisper

Hal Daume III:
>Here's the basic idea.  Suppose we have the function:
>
>> sum [] acc = acc
>> sum (x:xs) acc = sum xs (acc+x)
>
>This is tail recursive, but not strict in the accumulator argument.
...

Just a nitpick here. sum is indeed strict in its second argument (given that
(+) is strict in its first argument). That is, sum l _|_ = _|_ for all
possible lists l.

It is of course possible that the compiler you use does not detect this and
generates nonstrict code.

But I think a decent strictness analyzer should detect this. Can the problem
be that + is overloaded in Haskell, so the compiler cannot assume any
semantical properties like strictness for it?

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



Re: Isn't this tail recursive?

2002-03-12 Thread Jyrinx

Aha! Gotcha. Thanks for the explanation.

I suppose that, in general, for tail recursion to work right, the
accumulator has to be evaluated strictly (as is how my code was fixed)?

Jyrinx
[EMAIL PROTECTED]

On Tue, 2002-03-12 at 09:34, Hal Daume III wrote:
> Here's the basic idea.  Suppose we have the function:
> 
> > sum [] acc = acc
> > sum (x:xs) acc = sum xs (acc+x)
> 
> This is tail recursive, but not strict in the accumulator argument.  What
> this means is that the computation will be performed lazily, so sum
> [4,5,8,10,14,20] 0 will go like this:
> 
> > sum [4,5,8,10,14,20] 0 = 
> > sum [5,8,10,14,20] (0+4) =
> > sum [8,10,14,20] ((0+4)+5) =
> > sum [10,14,20] (((0+4)+5)+8) =
> > sum [14,20] 0+4)+5)+8)+10) =
> > sum [20] (0+4)+5)+8)+10)+14) =
> > sum [] ((0+4)+5)+8)+10)+14)+20) =
> > ((0+4)+5)+8)+10)+14)+20)
> 
> this computation in the accumulator argument won't be evaluated until you
> try to print it or something, which will reduce it and perform the
> computation.  this means that for a list of length n, the the sum
> computation will grow in size O(n).  what you need is to make sure that
> the computation is done strictly and that is done using seq or $!, as in:
> 
> > sum2 [] acc = acc
> > sum2 (x:xs) acc = sum2 xs $! (acc+x)
> 
> this means that "acc+x" will be computed at each step, so the accumulator
> will hold only the integer (or whatever type) and not the thunk (the
> computation).
> 
> the type of "$!" is the same as "$":
> 
> > $! :: (a -> b) -> a -> b
> 
> the sematics of $! are:
> 
> > f $! a = f a
> 
> but the difference is that $! causes "a" to be reduced completely, so it
> won't build a huge thunk.
> 
> at least that's my understanding; i'm willing to be corrected :)
> 
>  - Hal
> 
> --
> Hal Daume III
> 
>  "Computer science is no more about computers| [EMAIL PROTECTED]
>   than astronomy is about telescopes." -Dijkstra | www.isi.edu/~hdaume
> 
> On 11 Mar 2002, Jyrinx wrote:
> 
> > > > Normal  -> countAll' cs 0 nl (nw + newWord) (nc + 1)
> > > > White   -> countAll' cs 1 nl nw (nc + 1)
> > > > Newline -> countAll' cs 1 (nl + 1) nw (nc + 1)
> > > 
> > > 
> > > make this something like
> > > 
> > > ...
> > > 
> > >   Normal -> nw' `seq` nc' `seq` countAll' cs 0 nl nw' nc'
> > >   White  -> nc' `seq`   countAll' cs 1 nl nw  nc'
> > >   Newline-> nl' `seq` nc` `seq` countAll' cs 1 nl' nw nc'
> > > where nw' = nw + newWord
> > >   nc' = nc + 1
> > >   nl' = nl + 1
> > 
> > Cool! That did the trick ... (runs on very little memory *and* time now
> > ... very cool) I've read through the other responses (thanks all!), and
> > I'm still not exactly sure what's going on ... I'm relatively new to
> > Haskell, and my understanding of laziness is hardly rigorous; in
> > general, how should I know where I need to use seq, and what I need to
> > use it on? Is there a paper I should read? (I've got Hudak's book, but
> > it does everything lazily IIRC)
> > 
> > Jyrinx
> > [EMAIL PROTECTED]
> > 
> 
> ___
> Haskell mailing list
> [EMAIL PROTECTED]
> http://www.haskell.org/mailman/listinfo/haskell


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



Re: HGL ang GHC on Win32

2002-03-12 Thread Alastair David Reid


> When I compile a program using GHC 5.02.2 on Windows 200 using HGL,

I don't have GHC installed on my Windows partition (nor space for it,
I suspect) so I'll ask some questions and hope they suggest an answer.

Does it work ok using Hugs and HGL?

   Sigbjorn Finne did a great job of packaging both Hugs and HGL as
   .msi files so it should be quick to check.

   Be sure to use December 2002 Hugs and version 2.0.4 HGL (i.e., the
   versions currently on the web pages.

Any luck using ghci?  (Unlikely to be any better)

Does rebooting your machine help?  (This is one of the larger straws
 I'm going to grasp at.)

> when I run the exe, the window starts out initially as wide as my
> screen and only as tall as the title bar, regardless of what is
> passed as the dimensions to openWindow.  What gives?

I haven't heard of this before.

A quick glance at the code doesn't suggest anything.

Grasping at straws, here's an implausible story for what is going
wrong (doesn't suggest how it would work for other people but not for
you):

  If you use openWindow, the position on the screen is not specified
  (just the size).  In Haskell, this is expressed as Nothing but in
  (this corner of) the Win32 API, it is expressed by specifying
  -1 for the X and Y position.

  It is just possible that something has gone wrong in how that -1 is
  passed over from Haskell to C and that this has somehow gotten
  confused with the window size.

  You could test this implausible theory by changing the openWindow
  call in HelloWorld to read

w <- openWindowEx "Hello World Window" 
  (Just (100,100)) (300, 300) 
  Unbuffered Nothing
  
> If I resize the window everything works fine, but in my own
> application resizing the window causes it to report some error about
> arithmetic being bigger than 32 bits...

This might agree with my theory about -1's being passed around.
The -1 might somehow come back as the maximum unsigned int 0x
and almost any arithmetic operation on that would lead to overflow.
Except that GHC doesn't detect overflow...

> Any ideas?

No good ones.

I'm hoping that a GHC honcho will say 

  "Well of course that happens with 5.02.2 - you should upgrade to 5.03
  right away."

or some such.

Sorry I can't be more help,

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



Re: Isn't this tail recursive?

2002-03-12 Thread Jay Cox

On Tue, 12 Mar 2002, Hal Daume III wrote:

> Here's the basic idea.  Suppose we have the function:
>
> > sum [] acc = acc
> > sum (x:xs) acc = sum xs (acc+x)
>
> This is tail recursive, but not strict in the accumulator argument.  What
> this means is that the computation will be performed lazily, so sum
> [4,5,8,10,14,20] 0 will go like this:
>
> > sum [4,5,8,10,14,20] 0 =
> > sum [5,8,10,14,20] (0+4) =
> > sum [8,10,14,20] ((0+4)+5) =
> > sum [10,14,20] (((0+4)+5)+8) =
> > sum [14,20] 0+4)+5)+8)+10) =
> > sum [20] (0+4)+5)+8)+10)+14) =
> > sum [] ((0+4)+5)+8)+10)+14)+20) =
> > ((0+4)+5)+8)+10)+14)+20)
>
> this computation in the accumulator argument won't be evaluated until you
> try to print it or something, which will reduce it and perform the
> computation.  this means that for a list of length n, the the sum
> computation will grow in size O(n).  what you need is to make sure that
> the computation is done strictly and that is done using seq or $!, as in:
>
> > sum2 [] acc = acc
> > sum2 (x:xs) acc = sum2 xs $! (acc+x)
>
> this means that "acc+x" will be computed at each step, so the accumulator
> will hold only the integer (or whatever type) and not the thunk (the
> computation).
>
> the type of "$!" is the same as "$":
>
> > $! :: (a -> b) -> a -> b
>
> the sematics of $! are:
>
> > f $! a = f a
>
> but the difference is that $! causes "a" to be reduced completely, so it
> won't build a huge thunk.

I hate to say it, but my understanding of it is that it isnt so simple
(which could be good or bad depending upon your view).

I guess he best i can describe it is that it will force a to weak head
normal form (which is the same as being reduced completely
for expressions with only integers, or whatever...)

For instance, forcing x=(map f) $! [1..] will essentially force [1.. to
(1: (thunk generating [2..]) just before the (map f) is applied.  I
think.  Ok maybe that was a bad example but I can't really think of a good
one right now.

You might add something that it isn't the (+) operator thats generating
the thunks. It is the fact (and only this!) that (+) isn't being forced.
I always got confused how (+) could be strict in both arguments, at least
for the primitives Float, Integer, and the like, yet still apparently
generate a bunch of thunks, like in your expression
((0+4)+5)+8)+10)+14)+20).  Appearances can be deceiving.  But, once
that outermost expression is forced, the forcing moves down toward the
innermost expression and then the whole expression implodes into a value.
I guess the confusion was I somehow conjectured that the application of a
strict function to a value would cause haskell to apply that function
strictly, when in fact it should not and does not and I was plainly wrong.

Here is a short "proof"

bottom::[Int]
bottom=bottom
--bottom = _|_


y = const 3
-- const v = \x -> v

main=print (y (head bottom))

If my conjecture was right, main would not terminate. (head is a strict
function being applied to _|_ ).  However we know that since y = \x -> 3,
y will not force x, therefore main will print 3.

However... all one needs to do is to change the above to.

main=print (y $! (head bottom))

_|_ should be, propagated to main by the following deductions: head
_|_ = _|_, y $! _|_ = _|_, print _|_ = _|_. thus main = _|_.

Ooh, interesting.  I tried that in ghc 5.00 and in fact ghc is smart
enough
to detect bottom here! It says


>[jay@localhost haskell]$ ./a.out
>
>Fail: <>

awesome!

I feel like I am rambling to no end. alright. I hope I haven't
been too confusing here.


All in all I do like your explanation though.  Oh, and after I went to the
trouble to write this, I see that you did correct yourself.  All my work
all for naught! Maybe somebody will get something from my ramblings.


Thanks,

Jay Cox

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



Re: Isn't this tail recursive?

2002-03-12 Thread Hal Daume III

Oops, I made a false statement:

> > f $! a = f a
> 
> but the difference is that $! causes "a" to be reduced completely, so it
> won't build a huge thunk.

This isn't true.  $! will only perform one reduction, so for instance:

> id $! (a+1,b+1)

will not cause a+1 and b+1 to be calculated; it will only perform the
computation which creates the tuple.  similarly,

> id $! [a+5]

will not cause a+5 to be calculated, it will only result in the list being
created (i.e., reduced from a computation which will compute [a+5] to
simply the value [a+5]).  if you want what i was talking about, use the
DeepSeq module (http://www.isi.edu/~hdaume/haskell/Util/DeepSeq.hs) and
then you can write:

> id $!! [a+5]

which will actually perform the calculation.

 - Hal

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



TrafficMagnet - Special Offer!

2002-03-12 Thread Christine Hall









 


 


 
 

 
Hi!

Did you know that 85% of your potential customers will be using 
search engines to find what they are looking for on the Internet? 
Have you ever thought about getting your website listed on search 
engines worldwide?

TrafficMagnet offers a unique technology that will submit your 
website to over 300,000 search engines and directories every 
month. We can help your customers find you!

 


 


 

 




 
 

 
Normal Price:
$14.95
per month

 
Special Price:
$9.95
per month

 
You Save:
More than 30% off

 
 

 






 





 
Benefit now!
It's easy, it's affordable and you can sign up online.
I look forward to hearing from you.

 


Best Regards,

Christine Hall 
Sales and Marketing 
E-mail: [EMAIL PROTECTED] 
http://www.TrafficMagnet.net 










 This email was sent to [EMAIL PROTECTED] We understand you may wish NOT to receive information from us by eMail. To be removed from this and other offers, simply click here.





Re: uniqueness typing

2002-03-12 Thread Dana Harrington


Andre W B Furtado wrote:
> I found the following text when visiting the Clean (a functional language)
> site:
> 
> "Clean is the only functional language in the world which has a special type
> system, uniqueness typing. It enables to update function arguments
> destructively retaining the purity of the language."

I believe Mercury borrowed their uniqueness type (mode) system from 
Clean. But since Mercury is functional/logical then I guess its still 
true that Clean is the only functional language with a uniqueness type 
system.

> Then I have some questions:
> 1. Can anyone explain what does "update function arguments destructively"
> mean?

Uniquely typed values are guaranteed to be referenced at most once under 
program evaluation, these values can be modified in-place. As an 
example, suppose I have an array and I want to modify an element.  In 
general I need to create a whole new copy of the array in order to make 
the modification since there may be other places in the program that 
require access to the old array.  However, if I know that the old array 
has no other references (because the array has a unique type) then I do 
not need to make a copy, I can just modify the original array.  This has 
obvious efficiency benefits.

> 2. If this is a desirable thing, why does Haskell not implement it?

- Uniqueness types, of course, require replacing the type system, this 
is a non-trivial task,
- Destructive updates can already be accomplished with compiler 
supported libraries using monads,
- Uniqueness types invalidate some program transformations.

On the other hand I think uniqueness types are quite useful. 
Particularly as they allow much more flexible interaction between 
mutable data-structures than monadic approaches.  I don't know of any 
concrete reasons a uniqueness type system couldn't be added to Haskell.

This seems like a fine time to insert a plug for my Master's thesis, 
which describes a denotational semantics of uniqueness types:
http://www.cpsc.ucalgary.ca/~danaha/uniqueness-types.ps

Dana

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



uniqueness typing

2002-03-12 Thread Andre W B Furtado

I found the following text when visiting the Clean (a functional language)
site:

"Clean is the only functional language in the world which has a special type
system, uniqueness typing. It enables to update function arguments
destructively retaining the purity of the language."

Then I have some questions:
1. Can anyone explain what does "update function arguments destructively"
mean?
2. If this is a desirable thing, why does Haskell not implement it?

Thanks,
-- Andre

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



Re: Isn't this tail recursive?

2002-03-12 Thread Hal Daume III

Here's the basic idea.  Suppose we have the function:

> sum [] acc = acc
> sum (x:xs) acc = sum xs (acc+x)

This is tail recursive, but not strict in the accumulator argument.  What
this means is that the computation will be performed lazily, so sum
[4,5,8,10,14,20] 0 will go like this:

> sum [4,5,8,10,14,20] 0 = 
> sum [5,8,10,14,20] (0+4) =
> sum [8,10,14,20] ((0+4)+5) =
> sum [10,14,20] (((0+4)+5)+8) =
> sum [14,20] 0+4)+5)+8)+10) =
> sum [20] (0+4)+5)+8)+10)+14) =
> sum [] ((0+4)+5)+8)+10)+14)+20) =
> ((0+4)+5)+8)+10)+14)+20)

this computation in the accumulator argument won't be evaluated until you
try to print it or something, which will reduce it and perform the
computation.  this means that for a list of length n, the the sum
computation will grow in size O(n).  what you need is to make sure that
the computation is done strictly and that is done using seq or $!, as in:

> sum2 [] acc = acc
> sum2 (x:xs) acc = sum2 xs $! (acc+x)

this means that "acc+x" will be computed at each step, so the accumulator
will hold only the integer (or whatever type) and not the thunk (the
computation).

the type of "$!" is the same as "$":

> $! :: (a -> b) -> a -> b

the sematics of $! are:

> f $! a = f a

but the difference is that $! causes "a" to be reduced completely, so it
won't build a huge thunk.

at least that's my understanding; i'm willing to be corrected :)

 - Hal

--
Hal Daume III

 "Computer science is no more about computers| [EMAIL PROTECTED]
  than astronomy is about telescopes." -Dijkstra | www.isi.edu/~hdaume

On 11 Mar 2002, Jyrinx wrote:

> > > Normal  -> countAll' cs 0 nl (nw + newWord) (nc + 1)
> > > White   -> countAll' cs 1 nl nw (nc + 1)
> > > Newline -> countAll' cs 1 (nl + 1) nw (nc + 1)
> > 
> > 
> > make this something like
> > 
> > ...
> > 
> >   Normal -> nw' `seq` nc' `seq` countAll' cs 0 nl nw' nc'
> >   White  -> nc' `seq`   countAll' cs 1 nl nw  nc'
> >   Newline-> nl' `seq` nc` `seq` countAll' cs 1 nl' nw nc'
> > where nw' = nw + newWord
> >   nc' = nc + 1
> >   nl' = nl + 1
> 
> Cool! That did the trick ... (runs on very little memory *and* time now
> ... very cool) I've read through the other responses (thanks all!), and
> I'm still not exactly sure what's going on ... I'm relatively new to
> Haskell, and my understanding of laziness is hardly rigorous; in
> general, how should I know where I need to use seq, and what I need to
> use it on? Is there a paper I should read? (I've got Hudak's book, but
> it does everything lazily IIRC)
> 
> Jyrinx
> [EMAIL PROTECTED]
> 

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



RE: Haskell report: deriving Show & Read instances, Appendix D

2002-03-12 Thread Simon Peyton-Jones

Folks

Olaf points out a problem with the specification of 'deriving' Show.
In particular:

|  "The representation will be enclosed in parentheses 
| if the precedence of the top-level constructor operator in x 
| is less than d." 

Olaf proposes that we should change "less than" to "less than or equal
to".

His reasoning is below, and seems persuasive to me.  Briefly, the 
consequences of the change would be:

a) The current specification yields syntactically incorrect Haskell for
some associativities.  The changed specification would avoid this.

b) The changed spec would yield more than the minimum number
of parentheses.

c) The current spec makes it hard for simple recursive descent
parsers, such as that suggested by the Report for Read, to avoid
divergence on left recursion. The changed spec makes it easy.

d) The downside is that all compilers would need to change, slightly.

Any comments?

Simon


| In all Haskell implementations (tested Hugs,Ghc and nhc98) 
| show sometimes produces output that does not represent 
| well-formed expressions. For example:
| 
| data Tree a = Node a | Tree a :^: Tree a | Tree a ::: Tree a 
|   deriving (Eq,Show)
| 
| infixl 6 :::
| infixr 6 :^:
| 
| main = print ((Node True :^: Node False) ::: Node True)
| 
| yields
| 
| Node True :^: Node False ::: Node True
| 
| The expression is ill-formed because one constructor is left- 
| and the other one is right-associative.
| 
| Finally, left-recursive data constructors that are 
| left-associative lead read into infinite recursion. Example:
| 
| infixl 5 :^:
|   
| data Tree a =  Leaf a  |  Tree a :^: Tree a deriving (Show,Read)
| 
| main = do
|   print (read "(Leaf True :^: Leaf False) :^: Leaf True" :: Tree Bool)
| 
| 
| I have a solution for the two last problems. It means all 
| Haskell compilers have to change, but I believe that it is worth it.
| 
| The source of the show problem is that show tries to handle 
| associativity of infix constructors. But there is no way to 
| do this correctly. showsPrec gets as argument the precedence 
| of the surounding expression, but not its associativity. This 
| associativity would be needed to use associativity of 
| constructors correctly.
| 
| The solution is simple: dont' try to use associativity to 
| avoid parenthesis. Thus you get some superfluous paranthesis, 
| but the output is always correct and the implementation of 
| deriving is even a bit simpler. E.g.:
| 
| showsPrec d (u :^: v) = showParen (d > 5) showStr
| where
|showStr = showsPrec 6 u . 
|  showString " :^: " .
|  showsPrec 6 v
| For all of
| 
| infix 5 :^:
| infixl 5 :^:
| infixr 5 :^:
| 
| The second advantage of this simplification is, that the 
| additional parentheses prevent infinite left recursion. You 
| can read in the tree expression given above, because 
| parentheses are now compulsory:
| 
|   instance (Read a) => Read (Tree a) where
| 
|   readsPrec d r =  readParen (d > 5)
|(\r -> [(u:^:v,w) |
|(u,s) <- readsPrec 6 r,
|(":^:",t) <- lex s,
|(v,w) <- readsPrec 6 t]) r
| 
| ++ readParen (d > 9)
|(\r -> [(Leaf m,t) |
|("Leaf",s) <- lex r,
|(m,t) <- readsPrec 10 s]) r
| 
| What do you think?
| 
| Discussing all the other minor problems with the report 
| specification doesn't make sense before this major issue is 
| cleared up.
| 
| Ciao,
| Olaf
| 
| -- 
| OLAF CHITIL, 
|  Dept. of Computer Science, The University of York, York YO10 
| 5DD, UK. 
|  URL: http://www.cs.york.ac.uk/~olaf/
|  Tel: +44 1904 434756; Fax: +44 1904 432767
| 
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



FW: H98 Report: expression syntax glitch

2002-03-12 Thread Simon Peyton-Jones

In response to my recent message (below), Ross asks:

"Are you rejecting the fix I suggested:

Add a side condition to the grammar in 3.13: the guard must not
end with a type signature (because the following -> looks like
part of the type)."

Indeed, this would be possible.  It would reject programs like
f x = case x of { (a,b) | b :: Bool -> a }
which are in principle reasonable, but are really hard to parse.
Indeed, GHC, Hugs, and nhc all reject it.

I suppose that the term "ends with" is a bit imprecise, too.  Presumably
this would be OK
f x = case x of { (a,b) | (b :: Bool) -> a }

Still, Ross's suggestion is pragmatic: if all the impls find this corner
of the language too hard to parse, then some guidance about what 
not to write would be a good plan.

As usual, this is not a big deal: it's a dark corner that few will trip
over.  But it is my joyful task (aided by many others) to try to 
illuminate the darkness, so I invite your opinions about which
fix (the one below, or Ross's) is better.

Simon

-Original Message-
From: Ross Paterson [mailto:[EMAIL PROTECTED]] 
Sent: 11 March 2002 17:59
To: Simon Peyton-Jones
Subject: Re: H98 Report: expression syntax glitch


Simon,

> Ross points out that this is really hard to parse:
> 
> | case x of y | ($ True) $ \ z -> z :: Bool -> Bool -> y
> 
> because the parser doesn't know when to stop eating the type and treat

> the arrow as the case-alternative arrow.

> But in neither case can I see a cure that is better than the
> disease.  Remember, large-scale fixes are out of court.

An easier case than Carl's, I think.
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



FW: Layout indentation marking

2002-03-12 Thread Simon Peyton-Jones

I agree with Ian here (and not just because of what GHC does!)

Does anyone disagree?

Simon

-Original Message-
From: Ian Lynagh [mailto:[EMAIL PROTECTED]] 
Sent: 10 March 2002 15:23
To: Haskell list
Subject: Layout indentation marking



Given this module

module Main where

main :: IO()
main = putStrLn $ show $ foo

foo :: Int
foo = x + y
  where x = 6
s = "foo\
  \bar" y = 7

nhc98 and hugs correctly (as per the revised report) print 13. ghc gives

q.lhs:11: parse error on input `='

I think ghc is in the right here and the report should be updated to
read

  + Where the start of a lexeme does not follow the end of a lexeme
on
the same line, this lexeme is preceded by  where n is the
indentation of the lexeme, provided that it is not, as a
consequence of the first two rules, preceded by {n}. (A string
literal may span multiple lines -- Section 2.6.)

(it currently reads

  + Where the start of a lexeme does not follow a complete lexeme on
the same line, this lexeme is preceded by  where n is the
indentation of the lexeme, provided that it is not, as a
consequence of the first two rules, preceded by {n}. (A string
literal may span multiple lines -- Section 2.6.)

where I have altered only the first line).


Thanks
Ian

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



Re: A Cygwin port of hmake?

2002-03-12 Thread Malcolm Wallace

Antony,

> But unfortunately the Makefile.inc used to build hmake does some tricky 
> $(PWD) shenanigans that have nothing to do with configure, and then 
> passes the resulting path to ghc.  Unfortunately, $(PWD) returns 
> Cygwin-style paths, and I failed to find a good workaround for this in 
> the few minutes I spent looking at it.

David Duke recently reported that the hmake distributed with
nhc98-1.10 builds correctly with ghc-5.02.2 under Cygwin, but the
separate distribution of hmake-3.01 does not.  This was very puzzling,
but your mention of $(PWD) rings a bell as to what the difference
between them might be.  The working distribution uses $(shell pwd)
in its Makefiles instead of $(PWD).

I recently changed all instances of the former to the latter because I
couldn't see any reason why we should fork off lots of shell processes
just to find the current directory, when that information is instantly
available in a variable.  It seems that the slight performance hit
entailed by the shell calls is a necessary evil in order to cope with
Cygwin, so I'll change them back again.

Apologies for the inconvenience I have caused you by introducing this
simple "improvement".  It looked benign at the time!

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



RE: first-class polymorphism beats rank-2 polymorphism

2002-03-12 Thread Simon Peyton-Jones

| Ok, that's what I meant: in RHSs of other type synonyms.
| BTW, it also works when passing parameters to parameterized 
| datatypes. Here is a variation on defining Generic as a 
| datatypes as opposed to the earlier type synonym. Id is still 
| the same type synonym as before.
| 
| data Generic' i o = G (forall x. i x -> o x)
| type TP = Generic Id Id
| 
| Yes, I was surprised to see that it works to this extent.

This works because you said Generic not Generic' in the
RHS of TP.  If you use Generic' the program is rejected, and so
it should be.

| system would ask for. So I revise my question: Does the
| current support for partially applied type synonyms 
| pose any challenges or is it basically just like macro 
| expansion? That is, is the type system maybe not even 
| affected by it? If it is easy, why is not in Haskell 98 and 
| in hugs? It is terribly useful.

It's just macro expansion.  GHC expands saturated type synonyms
before looking for well-formedness in types.  This is indeed 
rather useful, and it's easy too.  It's not in H98 because no one
thought
of it then. 

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



minor H98 inconsistency: sections

2002-03-12 Thread Ross Paterson

The following passages differ on the status of (a+b+):

   3  Expressions

   aexp -> ...
 | ( expi+1 qop(a,i) )   (left section)
 | ( qop(a,i) expi+1 )   (right section)

   3.5  Sections

   Syntactic precedence rules apply to sections as follows.  (op e) is
   legal if and only if (x op e) parses in the same way as (x op (e));
   and similarly for (e op). For example, (*a+b) is syntactically invalid,
   but (+a*b) and (*(a+b)) are valid. Because (+) is left associative,
   (a+b+) is syntactically correct, but (+a+b) is not; the latter may
   legally be written as (+(a+b)).

ghc follows the grammar, rejecting (a+b+)
Hugs accepts (op a op' b) and rejects (a op b op') regardless of
associativity and precedence, while nhc accepts them both.

The grammar could be made to match the text by adding two alternatives:

 | ( lexpi qop(l,i) )   (left section)
 | ( qop(r,i) rexpi )   (right section)

Changing the text to match the grammar seems less attractive.

But the text says more than the revised grammar.  For example, it deals
with the expression glitch I mentioned the other week: together with
the disambiguation meta-rule, it implies that the expression

(let x = 10 in x `div`)

is invalid, because

let x = 10 in x `div` z

doesn't parse as (let x = 10 in x) `div` z

(might be worth adding this as an example)
but it's no help with SimonM's example

let x = 10 in x == x == True
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



RE: first-class polymorphism beats rank-2 polymorphism

2002-03-12 Thread Simon Peyton-Jones

| type Generic i o = forall x. i x -> o x
| 
| type Id x = x
| 
| comb :: 
| (Generic Id Id)
|  -> (Generic Id Id)   
|  -> (Generic Id Id)   
| comb = undefined

| So now let's ask for the type of comb in ghc.
| It turns out to be the rank-1 (!!!) type I captured as 
| explicit type annotation for comb'. I would have expected a 
| rank-2 type because the forall is scoped by the type synonym 
| Generic. So why should I like to see the forall going to the 
| top? I still would say that THIS IS A BUG. Here is why the 

Yes, indeed this is a bug.  Thank you for finding it.  It turned out
that in liberalising GHC's treatment of type synonyms (which you
remark is a good thing) I had failed to cover a case.   Fortunately,
an ASSERT caught the bug in my build, and the fix is easy.

| yacomb1 :: (forall x. x -> x) 
|   -> (forall x. x -> x) 
|   -> (forall x. x -> x) 
| yacomb1 =  (.)
|
| yacomb2 :: forall x y z. (x -> x) -> (y -> y) -> (z -> z)
| yacomb2 = undefined
|
| Now let's try to define yacomb2 in terms of yacomb1, that is:
|
| yacomb2 = yacomb1
|
| This works. Let us not wonder why.

We should wonder why.  It's plain wrong.  yacomb1's type signature
is more restrictive than that of yacomb2.   This is a bug in the 5.03
snapshot, which fortunately I fixed a week or two ago.  The compiler
in the respository rejects the definition.


Bottom line: you found two bugs, for which much thanks.  But I stand
by forall-lifting!   (But note that the foralls are lifted only from
*after*
the arrow, not before.   (forall a.a->a) -> Int   is not the same as
(forall a.  (a->a) -> Int).)

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



Re: Concurrent Haskell (GHC) and Win32 Applications ?

2002-03-12 Thread Ketil Z. Malde

"Simon Peyton-Jones" <[EMAIL PROTECTED]> writes:

> | Ahem - how far would this be from a "real" multithreaded 
> | implementation, i.e. one that could use a few OS threads to 
> | take advantage of multiple CPUs in an SMP system?

> Not very far.  We have had a working implementation of 
> such a thing, but not in a robust releasable state.

Really!?  Wow!

I have at my disposal an 8-CPU Sun and a (well, less disposable, but
access to, at any rate) a cluster of three 64-CPU Regattae.  I also
have at hand compute-heavy problems with a Haskell-implemented
solution.  Do let me know when you have something you'll let an
amateur with no compiler experience loose upon, won't you? :-)

When I last asked about, it seemed that parallell Haskell was the way
to go for performance gain, but sadly GPH is lagging real GHC a bit,
and worse, is using PVM for parallellisation.  As far as I understand,
this means a lot of heap duplication (which hurts, since I consume
lots of memory) and needless communication overhead on SMPs.

May I assume that, if/when a multithreaded RTS stabilises, the
paradigms from parallell Haskell can easily be implemented on it
("easily" meaning that it'll probably happen)?

At the moment, I'm working on getting my program correct, so I'm only
charting the waters, as it were, for parallellisation.

-kzm
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Your Email / Website Address

2002-03-12 Thread Online Notice

Warning
Unable to process data: 
multipart/related;boundary = "NextMimePart"




RE: Concurrent Haskell (GHC) and Win32 Applications ?

2002-03-12 Thread Simon Peyton-Jones

| Ahem - how far would this be from a "real" multithreaded 
| implementation, i.e. one that could use a few OS threads to 
| take advantage of multiple CPUs in an SMP system?

Not very far.  We have had a working implementation of 
such a thing, but not in a robust releasable state.

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