Re: Re[2]: [Haskell-cafe] FFI basics

2007-02-12 Thread Yitzchak Gale

Bulat Ziganshin wrote:

examples of lifting C functions into Haskell world:

mysin :: Double - Double
mysin = realToFrac . c_mysin . realToFrac

-- c_mysin :: CDouble - CDouble

rnd :: Int - IO Int
rnd x = do r - c_rnd (fromIntegral x)
   return (fromIntegral r)

-- c_rnd :: CInt - IO CInt


OK, got it. I'll put that in.

Thanks,
Yitz
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Optimization fun

2007-02-12 Thread Lennart Augustsson
Many architectures gives both the quotient and remainder when you use  
the division instruction, so divMod (quotRem) shouldn't cost more  
than a div or mod.  But if the code generator takes advantage of that  
is another matter.


On Feb 12, 2007, at 02:32 , Matthew Brecknell wrote:


I wrote:

primes :: [Int]
primes = 2 : filter isPrime [3,5..] where
  f x p r = x  p*p || mod x p /= 0  r
  isPrime x = foldr (f x) True primes


Creighton Hogg wrote:

This looks really slick to me, thanks.
So if I understand correctly, the main thing that makes this work  
is that
'ing the test with the accumulator r will make it bail out of  
the fold

as
soon as one of the two tests is failed because the result must be  
False?


Yes. Look at the definition of %% and ||:

True  x = x
False  _ = False

True || _ = True
False || x = x

The second argument of  or || won't be evaluated if the first
determines the result.

And this brings you back to the point made by Lennart and others about
why foldl is the wrong choice: foldl won't allow you to take advantage
of this short-circuiting. Write out a few steps of each type of  
fold if

you don't understand why.

Note, I wouldn't call r an accumulator: it's just the rest of the fold
(which, as you've pointed out, only needs to be evaluated if you don't
already know the result).

Since writing the above, I've realised that the second argument of the
foldr most certainly shouldn't be True. One might be able to argue  
that

False would be more correct, but really it's irrelevant since we know
we'll never reach the end of the list of primes. What I found most
surprising was that replacing True with undefined made the calculation
about 10% faster (GHC 6.4.2, amd64):


primes :: [Int]
primes = 2 : filter isPrime [3,5..] where
  f x p r = x  p*p || mod x p /= 0  r
  isPrime x = foldr (f x) undefined primes


Comparing this to DavidA's solution: At least on my platform,  
testing (x

 p*p) is significantly quicker than using quotRem/divMod. I suspect
quotRem actually requires the division to be performed twice, and
multiplication is faster than division.

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


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


[Haskell-cafe] Re: Optimization fun

2007-02-12 Thread DavidA
Lennart Augustsson lennart at augustsson.net writes:

 Yes, and that's pretty much what my version does (and what the  
 original tried to do?).

Yes, you're right, I see now that my method is equivalent to yours. (My 
apologies, it was late.)

The point I was trying to make is that there are two different ways to do it. 
The sieve method works by starting with the list [2..] (or [3,5..]), and 
successively filtering it to remove multiples as we discover each new prime. So 
the list starts out as [2,3,4,5..], then goes to [3,5,7,9..], then goes to 
[5,7,11,13..]. At each stage we're removing not just first element of the list, 
but all later elements divisible by it too. (eg in the last step we removed 9 
as well as 3)

The other method is to leave the list intact, and just test each element by 
trial division as we come to it.

The point is that the trial division method is much faster than the sieve 
method. Maintaining all those filter of filter of filter of ...  lists is 
hugely inefficient.

Intuitively I can see why, but it would be nice to have a good explanation.

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


Re: [Haskell-cafe] questions about core

2007-02-12 Thread Joel Reymont


On Feb 12, 2007, at 5:45 AM, Matt Roberts wrote:


 - The hackathon videos,
 - A transformation-based optimiser for Haskell,
 - An External Representation for the GHC Core Language (DRAFT for  
GHC5.02), and

 - Secrets of the Glasgow Haskell Compiler inliner.


Matt, can you please post pointers to the above?

Thanks, Joel

--
http://wagerlabs.com/





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


Re: [Haskell-cafe] questions about core

2007-02-12 Thread Joel Reymont


On Feb 12, 2007, at 7:06 AM, Stefan O'Rear wrote:

We have Core because Simon lacks the patience to solve the halting  
problem and

properly perform effects analysis on STG.

We have STG because Simon lacks the patience to wait for the 6.6  
Simplifier to

finish naively graph-reducing every time.


Are these two different Simons? :-)

--
http://wagerlabs.com/





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


Re: [Haskell-cafe] Foldr tutorial, Inspired by Getting a Fix from a Fold

2007-02-12 Thread Pixel
Chris Moline [EMAIL PROTECTED] writes:

 dropWhile p = foldr (\x l' - if p x then l' else x:l') []

invalid:  dropWhile ( 5) [1, 10, 1]  should return [10, 1]
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Foldr tutorial, Inspired by Getting a Fix from a Fold

2007-02-12 Thread Donald Bruce Stewart
pixel:
 Chris Moline [EMAIL PROTECTED] writes:
 
  dropWhile p = foldr (\x l' - if p x then l' else x:l') []
 
 invalid:  dropWhile ( 5) [1, 10, 1]  should return [10, 1]

Prelude Test.QuickCheck Text.Show.Functions quickCheck $ \p xs - dropWhile p 
xs == foldr (\x l' - if p x then l' else x:l') [] (xs :: [Int])

Falsifiable, after 4 tests:
function
[-1,-3,1]


If in doubt, do a quick check!

-- Don
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] questions about core

2007-02-12 Thread Dougal Stanton
Quoth Joel Reymont, nevermore,
 
 Are these two different Simons? :-)
 

I'm beginning to wonder if Simon is less a name and more a title,
meaning strong in the lambda force or somesuch. Let's hope they don't
go over to the dark side ;-)



-- 
Dougal Stanton
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Genuine Eratosthenes sieve [Was: Optimization fun]

2007-02-12 Thread Yitzchak Gale

[EMAIL PROTECTED] wrote:

Still, in the interest of purity, here it is, in
Haskell.  As the original Eratosthenes sieve,
this algorithm uses only successor and
predecessor operations.


I don't think the Greeks had too much trouble with
addition. If that is the case, then Rafael's
definition is still valid after a slight
modification, and still the clearest:

\begin{code}

-- Delete the elements of the first list from the second list,
-- where both lists are assumed sorted and without repetition.
deleteOrd :: Ord a = [a] - [a] - [a]
deleteOrd xs@(x:xs') ys@(y:ys')
 | x  y   = y : deleteOrd xs  ys'
 | x  y   = deleteOrd xs' ys
 | otherwise   = deleteOrd xs' ys'
deleteOrd _ ys = ys

sieve (x:xs) = x : sieve (deleteOrd [x+x,x+x+x..] xs)
sieve _  = []

primes = sieve [2..]

\end{code}

Regards,
Yitz
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] IO is not a monad

2007-02-12 Thread Yitzchak Gale

Lennart Augustsson wrote:

I'm not sure what you're asking.  The (untyped) lambda calculus is
Turing complete.
How could seq improve that?


Obviously, it can't. But how can it hurt?

Classical lambda calculus does not model the
semantics of laziness, so seq is equivalent to
flip const there, just like foldl' is equivalent
to foldl. If we modify the lambda calculus to
model laziness - let's say, by restricting
beta-reduction - then the interesting
properties of seq are revealed.

Why should we treat seq differently in Haskell
just because its interesting properties are not
modeled in the classical lambda calculus?
Haskell is not a classical language, it is
non-strict (among other differences).

Regards,
Yitz
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Very fast loops. Now!

2007-02-12 Thread Eric Willigers

Eric Willigers wrote:
Do the two programs implement the same algorithm? The C program updates 
x and y in sequence. The Haskell program updates x and y in parallel and 
can be easier for the compiler to optimize.



Hi Don,

Expressing this in other words, do we want the new y to be based on the 
new x or on the old x?


I extracted the code you posted to CS.c and HP.hs (C sequential, Hashell 
parallel).


I made the following minor changes to form CP.c and HS.hs (C parallel, 
Hashell sequential):-


double xn;
for (; i=10; i++) {
xn = x*y/3.0;
y = x*9.0;
x = xn;
}

| otherwise   = go xs (xs*9) (i+1)
where xs = x*y/3


Tested on a 2.8 GHz Pentium 4, running XP SP2 and cygwin, using the 
compiler options from your post. Each program was run once.


$ uname -a
CYGWIN_NT-5.1 nemo 1.5.21(0.156/4/2) 2006-07-30 14:21 i686 Cygwin

$ gcc --version
gcc (GCC) 3.4.4 (cygming special) (gdc 0.12, using dmd 0.125)

$ ghc --version
The Glorious Glasgow Haskell Compilation System, version 6.6


$ gcc -O3 -ffast-math -mfpmath=sse -msse2 -std=c99 CP.c -o CP

$ time ./CP
3.33

real0m10.560s
user0m10.546s
sys 0m0.015s


$ gcc -O3 -ffast-math -mfpmath=sse -msse2 -std=c99 CS.c -o CS

$ time ./CS
3.33

real0m10.788s
user0m10.718s
sys 0m0.015s


$ ghc -O -fexcess-precision -fbang-patterns -optc-O3 -optc-ffast-math 
-optc-mfpmath=sse -optc-msse2 HP.hs -o HP


$ time ./HP
3.3335

real1m8.550s
user0m0.015s
sys 0m0.031s


$ ghc -O -fexcess-precision -fbang-patterns -optc-O3 -optc-ffast-math 
-optc-mfpmath=sse -optc-msse2 HS.hs -o HS


$ time ./HS
3.3335

real1m9.425s
user0m0.015s
sys 0m0.046s


The differences between the P and S versions turned out to be incidental 
on my system.


I downloaded GHC a month ago. Should I be running a more recent build or 
using different compiler options?


Regards,
Eric.

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


Re[2]: [Haskell-cafe] Re: Optimization fun

2007-02-12 Thread Bulat Ziganshin
Hello Lennart,

Monday, February 12, 2007, 11:53:32 AM, you wrote:

 Many architectures gives both the quotient and remainder when you use
 the division instruction, so divMod (quotRem) shouldn't cost more  
 than a div or mod.  But if the code generator takes advantage of that
 is another matter.

qoutRem# is primitive operation in GHC

-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


Re: [Haskell-cafe] questions about core

2007-02-12 Thread Bulat Ziganshin
Hello Matt,

Monday, February 12, 2007, 8:45:47 AM, you wrote:

 I am trying to get a deeper understanding of core's role in GHC and

i'm not sure but may be these papers that say about STG can help you:

Implementing lazy functional languages on stock hardware: the
Spineless Tagless G-machine.
[http://research.microsoft.com/copyright/accept.asp?path=/users/simonpj/papers/spineless-tagless-gmachine.ps.gz]

[http://www.haskell.org/ghc/docs/papers/new-rts.ps.gz]
[http://www.haskell.org/ghc/docs/papers/run-time-system.ps.gz]


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


Re[2]: [Haskell-cafe] questions about core

2007-02-12 Thread Bulat Ziganshin
Hello Joel,

Monday, February 12, 2007, 12:23:16 PM, you wrote:
  - Secrets of the Glasgow Haskell Compiler inliner.

 Matt, can you please post pointers to the above?

mostly, these are available on papers pages of SM and SPJ:

http://research.microsoft.com/~simonpj/
http://research.microsoft.com/~simonpj/Papers/papers.html
http://research.microsoft.com/~simonmar/
http://www.haskell.org/~simonmar/bib/bib.html





-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


Re: [Haskell-cafe] FFI basics

2007-02-12 Thread Sven Panne
On Monday 12 February 2007 09:54, Yitzchak Gale wrote:
 Bulat Ziganshin wrote:
  examples of lifting C functions into Haskell world:
 
  mysin :: Double - Double
  mysin = realToFrac . c_mysin . realToFrac
 
  -- c_mysin :: CDouble - CDouble
 
  rnd :: Int - IO Int
  rnd x = do r - c_rnd (fromIntegral x)
 return (fromIntegral r)
 
  -- c_rnd :: CInt - IO CInt

 OK, got it. I'll put that in.

Just a small note here: GHC and the base library are both very careful to 
completely eliminate things like realToFrac or fromIntegeral in code similar 
to the one above, if the representations of the Haskell type and the C type 
are identical. Therefore there is no need to sacrifice portability for speed 
by leaving these conversion function out and making invalid assumptions. If 
actual conversion code is generated without a good reason, I would consider 
this as a bug.

Cheers,
   S.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Network.CGI.Compat.pwrapper

2007-02-12 Thread Gracjan Polak

Hi,

I wanted to setup really simple http server, found Network.CGI.Compat.pwrapper
and decided it suits my needs. Code:

module Main where
import Network.CGI
import Text.XHtml
import Network

doit vars = do
return (body (toHtml (show vars)))

main = withSocketsDo (pwrapper (PortNumber ) doit)


Pointng any browser to http://127.0.0.1: does not render the page. It seems
the response headers are broken.

How do I report this bug (trac? something else?).

We might want to either fix it, or just get rid of it, as nobody seems to notice
the problem :)

$ ghc --version
The Glorious Glasgow Haskell Compilation System, version 6.6

Tested under WinXP and MacOSX 10.4.9.

Another question is: how do I do equivalent functionality without pwrapper?

-- 
Gracjan



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


Re: [Haskell-cafe] Foldr tutorial, Inspired by Getting a Fix from a Fold

2007-02-12 Thread Nicolas Frisby

Guess this is a tricky choice for a foldr intro, since it requires a
paramorphism (see bananas lenses wires etc.)

para :: (a - [a] - b - b) - b - [a] - b
para f e [] = e
para f e (x:xs) = f x xs (para f e xs)

-- note that the original tail of the list (i.e. xs and not xs') is
used in the else-branch
dropWhile' p = para (\x xs xs' - if p x then xs' else (x:xs)) []

Prelude dropWhile' (5) [1,2,3,4,5,6,7,8]
[5,6,7,8]
Prelude dropWhile' (5) [1,2,3,4,5,6,7,1]
[5,6,7,1]
Prelude :m + Test.QuickCheck
Prelude Test.QuickCheck :m + Text.Show.Functions
Prelude Test.QuickCheck Text.Show.Functions
   quickCheck $ \p l - dropWhile p (l :: [Int]) == dropWhile' p l
Loading package QuickCheck-1.0 ... linking ... done.
OK, passed 100 tests.


On 2/12/07, Donald Bruce Stewart [EMAIL PROTECTED] wrote:

pixel:
 Chris Moline [EMAIL PROTECTED] writes:

  dropWhile p = foldr (\x l' - if p x then l' else x:l') []

 invalid:  dropWhile ( 5) [1, 10, 1]  should return [10, 1]

Prelude Test.QuickCheck Text.Show.Functions quickCheck $ \p xs - dropWhile p xs 
== foldr (\x l' - if p x then l' else x:l') [] (xs :: [Int])

Falsifiable, after 4 tests:
function
[-1,-3,1]


If in doubt, do a quick check!

-- Don
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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


[Haskell-cafe] pythags

2007-02-12 Thread phiroc
Hello,

the Advanced Monads page in the Haskell Wikibook
(http://en.wikibooks.org/wiki/Haskell/Advanced_monads) contains the following
example of a List Monad

pythags = do
x - [1..]
y - [x..]
z - [y..]
guard (x^2 + y^2 == z^2)
return (x, y, z)

However, whenever you load that function definition into Hugs or GHCi, you get a
message saying that guard is an undefined variable.

Does anyone know why?

Thanks.

phiroc
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] pythags

2007-02-12 Thread Greg Fitzgerald

Check out Hoogle:  http://haskell.org/hoogle/?q=guard

import Control.Monad

-Greg



On 2/12/07, [EMAIL PROTECTED] [EMAIL PROTECTED] wrote:


Hello,

the Advanced Monads page in the Haskell Wikibook
(http://en.wikibooks.org/wiki/Haskell/Advanced_monads) contains the
following
example of a List Monad

pythags = do
x - [1..]
y - [x..]
z - [y..]
guard (x^2 + y^2 == z^2)
return (x, y, z)

However, whenever you load that function definition into Hugs or GHCi, you
get a
message saying that guard is an undefined variable.

Does anyone know why?

Thanks.

phiroc
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

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


Re: [Haskell-cafe] pythags

2007-02-12 Thread Robert Dockins


On Feb 12, 2007, at 11:02 AM, [EMAIL PROTECTED] wrote:


Hello,

the Advanced Monads page in the Haskell Wikibook
(http://en.wikibooks.org/wiki/Haskell/Advanced_monads) contains the  
following

example of a List Monad

pythags = do
x - [1..]
y - [x..]
z - [y..]
guard (x^2 + y^2 == z^2)
return (x, y, z)

However, whenever you load that function definition into Hugs or  
GHCi, you get a

message saying that guard is an undefined variable.

Does anyone know why?

Thanks.

phiroc



Add the line


import Control.Monad


to the beginning of your program.  The 'guard' function is not  
automatically in scope.





Rob Dockins

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



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


Re: [Haskell-cafe] pythags

2007-02-12 Thread Creighton Hogg

On 2/12/07, [EMAIL PROTECTED] [EMAIL PROTECTED] wrote:


Hello,

the Advanced Monads page in the Haskell Wikibook
(http://en.wikibooks.org/wiki/Haskell/Advanced_monads) contains the
following
example of a List Monad

pythags = do
x - [1..]
y - [x..]
z - [y..]
guard (x^2 + y^2 == z^2)
return (x, y, z)

However, whenever you load that function definition into Hugs or GHCi, you
get a
message saying that guard is an undefined variable.

Does anyone know why?

Thanks.

phiroc



In the context of the tutorial, guard isn't defined until the next section:
additive monads.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] pythags

2007-02-12 Thread Robert Dockins


On Feb 12, 2007, at 11:02 AM, [EMAIL PROTECTED] wrote:


Hello,

the Advanced Monads page in the Haskell Wikibook
(http://en.wikibooks.org/wiki/Haskell/Advanced_monads) contains the  
following

example of a List Monad

pythags = do
x - [1..]
y - [x..]
z - [y..]
guard (x^2 + y^2 == z^2)
return (x, y, z)

However, whenever you load that function definition into Hugs or  
GHCi, you get a

message saying that guard is an undefined variable.

Does anyone know why?

Thanks.

phiroc



Another note about this function -- it doesn't actually work.  It  
will forever try increasing values of z, trying to find a z such that  
z^2 = 1^2 + 1^2, and no such z exists.  The following function,  
however, does seem to correctly generate all the Pythagorean triples.



pythags = do
   z - [1..]
   x - [1..z]
   y - [x..z]
   guard (x^2 + y^2 == z^2)
   return (x,y,z)






Rob Dockins

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



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


Re: [Haskell-cafe] questions about core

2007-02-12 Thread Kirsten Chevalier

On 2/11/07, Matt Roberts [EMAIL PROTECTED] wrote:

  - Exactly what are the operational and denotational semantics of core?


Since I don't think this question has been answered yet, here's a
mailing list post from  Simon PJ that probably answers it:
http://www.haskell.org/pipermail/glasgow-haskell-users/2003-February/004849.html

That's from 2003, but I don't think the answer has changed since then.
If you wrote down a precise operational and/or denotational semantics
for Core, you'd probably have a research paper. (Especially if you
proved that GHC actually obeys that semantics...) (Disclaimer: my name
isn't Simon.)

Cheers,
Kirsten

--
Kirsten Chevalier* [EMAIL PROTECTED] *Often in error, never in doubt
There are no sexist decisions to be made. There are antisexist
decisions to be made. And they require tremendous energy and
self-scrutiny, as well as moral stamina... -- Samuel R. Delany
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] questions about core

2007-02-12 Thread Kirsten Chevalier

On 2/12/07, Dougal Stanton [EMAIL PROTECTED] wrote:

Quoth Joel Reymont, nevermore,

 Are these two different Simons? :-)


I'm beginning to wonder if Simon is less a name and more a title,
meaning strong in the lambda force or somesuch. Let's hope they don't
go over to the dark side ;-)



I read that Simon means one who listens to or obeys God. Tying
this together with Stefan's post, maybe God is sort of like the
unwritten denotational semantics for Haskell.

Cheers,
Kirsten

--
Kirsten Chevalier* [EMAIL PROTECTED] *Often in error, never in doubt
Would you be my clock if I promise not to hang you / Too close to the window
or the picture of the pope? / I won't set you back and I won't push you
forward / I just want to look in your face and see hope -- Dom Leone
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Foldr tutorial, Inspired by Getting a Fix from a Fold

2007-02-12 Thread Bernie Pope

Nicolas Frisby wrote:

Guess this is a tricky choice for a foldr intro, since it requires a
paramorphism (see bananas lenses wires etc.)

para :: (a - [a] - b - b) - b - [a] - b
para f e [] = e
para f e (x:xs) = f x xs (para f e xs)

-- note that the original tail of the list (i.e. xs and not xs') is
used in the else-branch
dropWhile' p = para (\x xs xs' - if p x then xs' else (x:xs)) []
Actually, several people tried to use para, but of course it is not in 
the spirit of the challenge :)


Cheers,
Bernie.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] IO is not a monad

2007-02-12 Thread Lennart Augustsson

Adding seq ruins eta reduction.  For normal order lambda calculus
we have '\x.f x = f' (x not free in f).  If we add seq this is no  
longer true.


I'm not sure why you bring up lazy evaluation (I presume you
mean lazy evaluation as in call-by-need).  Having call-by-need
or not is unobservable, with or without seq.

I'm a fan of eta, it makes reasoning easier.  It also means
the compiler can do more transformations.

-- Lennart

On Feb 12, 2007, at 10:22 , Yitzchak Gale wrote:


Lennart Augustsson wrote:

I'm not sure what you're asking.  The (untyped) lambda calculus is
Turing complete.
How could seq improve that?


Obviously, it can't. But how can it hurt?

Classical lambda calculus does not model the
semantics of laziness, so seq is equivalent to
flip const there, just like foldl' is equivalent
to foldl. If we modify the lambda calculus to
model laziness - let's say, by restricting
beta-reduction - then the interesting
properties of seq are revealed.

Why should we treat seq differently in Haskell
just because its interesting properties are not
modeled in the classical lambda calculus?
Haskell is not a classical language, it is
non-strict (among other differences).

Regards,
Yitz


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


Re: [Haskell-cafe] Foldr tutorial, Inspired by Getting a Fix from a Fold

2007-02-12 Thread Nicolas Frisby

Oops; I totally forgot the context of this whole discussion!

I enjoyed your article.

On 2/12/07, Bernie Pope [EMAIL PROTECTED] wrote:

Nicolas Frisby wrote:
 Guess this is a tricky choice for a foldr intro, since it requires a
 paramorphism (see bananas lenses wires etc.)

 para :: (a - [a] - b - b) - b - [a] - b
 para f e [] = e
 para f e (x:xs) = f x xs (para f e xs)

 -- note that the original tail of the list (i.e. xs and not xs') is
 used in the else-branch
 dropWhile' p = para (\x xs xs' - if p x then xs' else (x:xs)) []
Actually, several people tried to use para, but of course it is not in
the spirit of the challenge :)

Cheers,
Bernie.


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


Re: [Haskell-cafe] Foldr tutorial, Inspired by Getting a Fix from a Fold

2007-02-12 Thread Lennart Augustsson

Sure, but we also have

para f e xs = snd $ foldr (\ x ~(xs, y) - (x:xs, f x xs y)) ([], e) xs

So I think using para is fine.

-- Lennart

On Feb 12, 2007, at 18:40 , Bernie Pope wrote:


Nicolas Frisby wrote:

Guess this is a tricky choice for a foldr intro, since it requires a
paramorphism (see bananas lenses wires etc.)

para :: (a - [a] - b - b) - b - [a] - b
para f e [] = e
para f e (x:xs) = f x xs (para f e xs)

-- note that the original tail of the list (i.e. xs and not xs') is
used in the else-branch
dropWhile' p = para (\x xs xs' - if p x then xs' else (x:xs)) []
Actually, several people tried to use para, but of course it is not  
in the spirit of the challenge :)


Cheers,
Bernie.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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


Re: [Haskell-cafe] questions about core

2007-02-12 Thread Robert Dockins


On Feb 12, 2007, at 1:31 PM, Kirsten Chevalier wrote:


On 2/11/07, Matt Roberts [EMAIL PROTECTED] wrote:
  - Exactly what are the operational and denotational semantics of  
core?


Since I don't think this question has been answered yet, here's a
mailing list post from  Simon PJ that probably answers it:
http://www.haskell.org/pipermail/glasgow-haskell-users/2003- 
February/004849.html


That's from 2003, but I don't think the answer has changed since then.
If you wrote down a precise operational and/or denotational semantics
for Core, you'd probably have a research paper. (Especially if you
proved that GHC actually obeys that semantics...) (Disclaimer: my name
isn't Simon.)


At the risk of sounding self-promoting, I'd like to point out that  
the research paper I recently announced defines an intermediate  
language that is similar to GHC's core in some respects (they are  
both based on System F_omega).  I give a full (call-by-name)  
operational semantics and type system for the language in my report  
[1].  You won't find any proofs in the paper, but they're on my  
medium-term agenda.  There is also source code for an interpreter/ 
bytecode-compiler/shell for this intermediate language [2].


[1] http://www.cs.tufts.edu/tr/techreps/TR-2007-2
[2] http://www.eecs.tufts.edu/~rdocki01/masters.html



Cheers,
Kirsten




Rob Dockins

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



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


Re: [Haskell-cafe] Network.CGI.Compat.pwrapper

2007-02-12 Thread Bjorn Bringert

On Feb 12, 2007, at 14:22 , Gracjan Polak wrote:

I wanted to setup really simple http server, found  
Network.CGI.Compat.pwrapper

and decided it suits my needs. Code:

module Main where
import Network.CGI
import Text.XHtml
import Network

doit vars = do
return (body (toHtml (show vars)))

main = withSocketsDo (pwrapper (PortNumber ) doit)


Pointng any browser to http://127.0.0.1: does not render the  
page. It seems

the response headers are broken.

How do I report this bug (trac? something else?).

We might want to either fix it, or just get rid of it, as nobody  
seems to notice

the problem :)

$ ghc --version
The Glorious Glasgow Haskell Compilation System, version 6.6

Tested under WinXP and MacOSX 10.4.9.


Hi Gracjan,

pwrapper is not an HTTP server, though the Haddock comment can make  
you think so. pwrapper allows you to talk *CGI* over a TCP port, but  
I have no idea why anyone would like to do that. The functions in the  
Network.CGI.Compat module are deprecated, and shouldn't be used in  
new code. Even though I'm the maintainer of the cgi package, I don't  
really know what those functions could ever be useful for, and I've  
never seen any code which uses them. In fact, I've now removed the  
Network.CGI.Compat module and uploaded cgi-3001.0.0 to Hackage.


Another question is: how do I do equivalent functionality without  
pwrapper?


You can roll you own web server if you want something very simple. If  
you don't want to do that, there is a version of Simon Marlow's  
Haskell Web Server with CGI support [1]. You could also get the  
original HWS [2] and merge it with your program. You might also be  
interested In HAppS [3].


/Björn

[1] http://www.cs.chalmers.se/~bringert/darcs/hws-cgi/
[2] http://darcs.haskell.org/hws/
[3] http://happs.org/___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Foldr tutorial, Inspired by Getting a Fix from a Fold

2007-02-12 Thread Bernie Pope

Lennart Augustsson wrote:

Sure, but we also have

para f e xs = snd $ foldr (\ x ~(xs, y) - (x:xs, f x xs y)) ([], e) xs

Nice one.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Very fast loops. Now!

2007-02-12 Thread Donald Bruce Stewart
ewilligers:
 Eric Willigers wrote:
 Do the two programs implement the same algorithm? The C program updates 
 x and y in sequence. The Haskell program updates x and y in parallel and 
 can be easier for the compiler to optimize.
 
 
 Hi Don,
 
 Expressing this in other words, do we want the new y to be based on the 
 new x or on the old x?
 
 I extracted the code you posted to CS.c and HP.hs (C sequential, Hashell 
 parallel).
 
 I made the following minor changes to form CP.c and HS.hs (C parallel, 
 Hashell sequential):-
 
 double xn;
 for (; i=10; i++) {
 xn = x*y/3.0;
 y = x*9.0;
 x = xn;
 }
 
 | otherwise   = go xs (xs*9) (i+1)
 where xs = x*y/3
 
 
 Tested on a 2.8 GHz Pentium 4, running XP SP2 and cygwin, using the 
 compiler options from your post. Each program was run once.
 
 $ uname -a
 CYGWIN_NT-5.1 nemo 1.5.21(0.156/4/2) 2006-07-30 14:21 i686 Cygwin
 
 $ gcc --version
 gcc (GCC) 3.4.4 (cygming special) (gdc 0.12, using dmd 0.125)
 
 $ ghc --version
 The Glorious Glasgow Haskell Compilation System, version 6.6
 
 
 $ gcc -O3 -ffast-math -mfpmath=sse -msse2 -std=c99 CP.c -o CP
 
 $ time ./CP
 3.33
 
 real0m10.560s
 user0m10.546s
 sys 0m0.015s
 
 
 $ gcc -O3 -ffast-math -mfpmath=sse -msse2 -std=c99 CS.c -o CS
 
 $ time ./CS
 3.33
 
 real0m10.788s
 user0m10.718s
 sys 0m0.015s
 
 
 $ ghc -O -fexcess-precision -fbang-patterns -optc-O3 -optc-ffast-math 
 -optc-mfpmath=sse -optc-msse2 HP.hs -o HP
 
 $ time ./HP
 3.3335
 
 real1m8.550s
 user0m0.015s
 sys 0m0.031s
 
 
 $ ghc -O -fexcess-precision -fbang-patterns -optc-O3 -optc-ffast-math 
 -optc-mfpmath=sse -optc-msse2 HS.hs -o HS
 
 $ time ./HS
 3.3335
 
 real1m9.425s
 user0m0.015s
 sys 0m0.046s


-fexcess-precision *must* be provided as a pragma, 

{-# OPTIONS -fexcess-precision #-}

import Text.Printf

main = go (1/3) 3 1

go :: Double - Double - Int - IO ()
go !x !y !i
| i == 10 = printf %.6f\n (x+y)
| otherwise   = go xn (xn*9) (i+1)
   where xn = x*y/3

C source:

#include stdio.h

int main()
{
double x = 1.0/3.0;
double y = 3.0;
int i= 1;
double xn;

for (; i10; i++) {
 xn = x*y/3.0;
 y = x*9.0;
 x = xn;
}

printf(%f\n, x+y);
return 0;
}





$ ghc -O2 -optc-O3 -optc-ffast-math -optc-mfpmath=sse -optc-msse2 
-fbang-patterns HP.hs -o hp
$ time ./hp 
 
3.33
./hp  17.59s user 0.01s system 99% cpu 17.646 total

$ gcc -O3 -ffast-math -mfpmath=sse -msse2 -std=c99 t.c -o cc
$ time ./cc
3.33
./cc  8.70s user 0.00s system 98% cpu 8.837 total




Now, if we rewrite it to not use the temporary:

go :: Double - Double - Int - IO ()
go !x !y !i
| i == 10 = printf %.6f\n (x+y)
| otherwise   = go (x*y/3) (x*9) (i+1)


for (; i10; i++) {
x = x*y/3.0;
y = x*9.0;
}



$ time ./hp
3.33
./hp  9.95s user 0.00s system 99% cpu 9.965 total

$ time ./cc 
3.33
./cc  10.06s user 0.00s system 99% cpu 10.110 total



$ gcc --version
gcc (GCC) 3.3.5 (propolice)

$ ghc --version
The Glorious Glasgow Haskell Compilation System, version 6.6

$ dmesg| grep cpu0 | head
cpu0: Intel(R) Pentium(R) M processor 1600MHz (GenuineIntel 686-class) 
1.60 GHz

-- Don
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] questions about core

2007-02-12 Thread Kirsten Chevalier

On 2/12/07, Robert Dockins [EMAIL PROTECTED] wrote:


At the risk of sounding self-promoting, I'd like to point out that
the research paper I recently announced defines an intermediate
language that is similar to GHC's core in some respects (they are
both based on System F_omega).  I give a full (call-by-name)
operational semantics and type system for the language in my report
[1].  You won't find any proofs in the paper, but they're on my
medium-term agenda.  There is also source code for an interpreter/
bytecode-compiler/shell for this intermediate language [2].

[1] http://www.cs.tufts.edu/tr/techreps/TR-2007-2
[2] http://www.eecs.tufts.edu/~rdocki01/masters.html



I was also neglectful in not mentioning this paper:

http://www.cse.unsw.edu.au/~chak/papers/SCPD07.html

System F with Type Equality Coercions
Martin Sulzmann, Manuel M. T. Chakravarty, Simon Peyton Jones, and
Kevin Donnelly. In G. Necula, editor, Proceedings of The Third ACM
SIGPLAN Workshop on Types in Language Design and Implementation, ACM
Press, 2007.

which describes System FC, which is the current incarnation of Core in GHC,
and in fact that paper *does* give an operational semantics for it.

Cheers,
Kirsten

--
Kirsten Chevalier* [EMAIL PROTECTED] *Often in error, never in doubt
It's important for us to explain to our nation that life is important. It's
not only life of babies, but it's life of children living in, you know,
the dark dungeons of the Internet. -- George W. Bush
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Very fast loops. Now!

2007-02-12 Thread David Roundy
On Tue, Feb 13, 2007 at 08:18:25AM +1100, Donald Bruce Stewart wrote:
 Now, if we rewrite it to not use the temporary:
 
 go :: Double - Double - Int - IO ()
 go !x !y !i
 | i == 10 = printf %.6f\n (x+y)
 | otherwise   = go (x*y/3) (x*9) (i+1)
 
 
 for (; i10; i++) {
 x = x*y/3.0;
 y = x*9.0;
 }
 
 
 
 $ time ./hp
 3.33
 ./hp  9.95s user 0.00s system 99% cpu 9.965 total
 
 $ time ./cc 
 3.33
 ./cc  10.06s user 0.00s system 99% cpu 10.110 total

I'm rather curious (if you're sill interested) how this'll be affected by
the removal of the division from the inner loop. e.g.

go :: Double - Double - Int - IO ()
go !x !y !i
| i == 10 = printf %.6f\n (x+y)
| otherwise   = go (x*y*(1.0/3)) (x*9) (i+1)


for (; i10; i++) {
x = x*y*(1.0/3.0);
y = x*9.0;
}

My guess is that the code will be far faster, and that the differences
between C and Haskell will therefore be more pronounced.  After all,
division is a slow operation...
-- 
David Roundy
Department of Physics
Oregon State University
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] IO is not a monad

2007-02-12 Thread Claus Reinke

Adding seq ruins eta reduction.  For normal order lambda calculus
we have '\x.f x = f' (x not free in f).  If we add seq this is no longer true.


isn't that a problem of seq (and evaluation in Haskell generally) not being 
strict enough (ie, forcing evaluation only to weak head normal form rather 
than to head normal form)?


for instance:

   seq (\x-_|_ x) () = () =/= _|_ = seq _|_ ()

but (assuming a variant, seq-hnf, forcing to hnf instead): 


   seq-hnf (\x- _|_ x ) () = _|_ = seq-hnf _|_ ()

I don't have my phone book here, but didn't Barendregt have a discussion
of what kind of normal form would be an appropriate choice for the meaning
of lambda terms, with hnf being good and whnf or nf being bad? reduction
to whnf is a pragmatic choice, with a long history, and its own calculus, which 
is not quite the ordinary lambda calculus.


but it's been ages since I learned these things, so I might be misremembering.

Claus


I'm a fan of eta, it makes reasoning easier.  It also means
the compiler can do more transformations.


I also like eta conversion, as well as its variations for non-function types. what 
they have in common is that the expanded form provides syntactic/structural 
evidence for properties that are only semantically present in the reduced 
form. for instance, if we add non-functions to the calculus, eta has to be
constrained with type information for f - as the expanded form promises 
that we have a function, holding more information than the reduced form.


variations of eta for non-function types, this allows us to make functions/
contexts less strict (the kind of borrowing information from the future so 
often needed in cyclic programming, or in dealing with other potentially 
infinite structures):


   lazy_id_pair x = (fst x,snd x)-- lazy_id_pair _|_ = (_|_,_|_)

vs

   strict_id_pair (a,b) = (a,b)-- strict_id_pair _|_ = _|_

at the expense of not having laws like:  


   x = (fst x,snd x)-- not true in general, even if we know that x::(a,b)

   x = x = return-- not true in general, even if x :: Monad m = m a

   x = \y- x y-- not true in general, even if x :: a - b

we still have the inequalities, though - the expanded form being more
defined than the reduced form.

   x :: t ]= (expand-at-t x) :: t-- eta conversion at type t

so compilers could use eta-expansion, but not eta-reduction (not without
an approximate analysis of an undecidable property). do you happen to 
have an example in mind where eta-reduction would be beneficial as a 
compiler transformation, but analysis (to demonstrate that the expanded 
functional expression terminates successfully) impractical?


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


Re: [Haskell-cafe] questions about core

2007-02-12 Thread Matt Roberts


On 12/02/2007, at 8:23 PM, Joel Reymont wrote:



On Feb 12, 2007, at 5:45 AM, Matt Roberts wrote:


 - The hackathon videos,



@electronic{hack06,
Author = {Simon Peyton Jones and Malcolm Wallace and et. al.},
Date-Added = {2007-02-13 09:04:47 +1100},
Date-Modified = {2007-02-13 09:06:09 +1100},
Title = {GHC Hackathon},
Url = {http://hackage.haskell.org/trac/ghc/wiki/Hackathon}}



 - A transformation-based optimiser for Haskell,



@article{jones98,
Author = {Simon L. {Peyton Jones} and Andr{\'e} L. M. Santos},
Date-Added = {2007-02-11 21:16:19 +1100},
Date-Modified = {2007-02-11 22:05:31 +1100},
Journal = {Science of Computer Programming},
Number = {1--3},
Pages = {3--47},
Title = {A transformation-based optimiser for {Haskell}},
Url = {citeseer.ist.psu.edu/peytonjones98transformationbased.html},
Volume = {32},
Year = {1998}}


 - An External Representation for the GHC Core Language (DRAFT  
for GHC5.02), and


-- these bibligraphic details are not complete yet
@electronic{Tolmach01,
Author = {Andrew Tolmach},
Date-Added = {2006-11-27 18:21:37 +1100},
Date-Modified = {2007-02-11 22:05:11 +1100},
	Title = {An External Representation for the GHC Core Language (DRAFT  
for GHC5.02)},

Urldate = {November 27 2006}}



 - Secrets of the Glasgow Haskell Compiler inliner.



@article{jones02,
Address = {New York, NY, USA},
Author = {Simon Peyton Jones and Simon Marlow},
Date-Added = {2007-02-11 21:25:16 +1100},
Date-Modified = {2007-02-11 21:26:58 +1100},
Doi = {http://dx.doi.org/10.1017/S0956796802004331},
Issn = {0956-7968},
Journal = {J. Funct. Program.},
Number = {5},
Pages = {393--434},
Publisher = {Cambridge University Press},
Rating = {3},
Title = {Secrets of the Glasgow Haskell Compiler inliner},
Volume = {12},
Year = {2002}}




Matt, can you please post pointers to the above?

Thanks, Joel

--
http://wagerlabs.com/







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


[Haskell-cafe] Re: Foldr tutorial, Inspired by Getting a Fix from a Fold

2007-02-12 Thread apfelmus
Bernie Pope wrote:
 Lennart Augustsson wrote:
 Sure, but we also have

 para f e xs = snd $ foldr (\ x ~(xs, y) - (x:xs, f x xs y)) ([], e) xs
 Nice one.

Nice one is an euphemism, it's exactly solution one :)

Regards,
apfelmus

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


[Haskell-cafe] Re: Parsec and Java

2007-02-12 Thread Benjamin Franksen
Arnaud Bailly wrote:
 Joel Reymont wrote:
 Is there a Java parser implemented using Parsec?
 There is:
 http://jparsec.codehaus.org/

Jparsec is an implementation of Haskell Parsec on the Java platform. I
think Joel was asking for a parser for the Java language, written in
Haskell using the (original, Haskell-) Parsec library. 

So much for natural language and ambiguities... ;-)

Ben

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


Re: [Haskell-cafe] Re: Very fast loops. Now!

2007-02-12 Thread Bryan O'Sullivan

David Roundy wrote:


I'm rather curious (if you're sill interested) how this'll be affected by
the removal of the division from the inner loop. e.g.

go :: Double - Double - Int - IO ()
go !x !y !i
| i == 10 = printf %.6f\n (x+y)
| otherwise   = go (x*y*(1.0/3)) (x*9) (i+1)


for (; i10; i++) {
x = x*y*(1.0/3.0);
y = x*9.0;
}


GCC will do the transformation itself if you use -ffast-math.  It 
requires the flag as the results aren't exactly numerically equivalent.


b
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Network.CGI.Compat.pwrapper

2007-02-12 Thread Albert Y. C. Lai

Bjorn Bringert wrote:
pwrapper is not an HTTP server, though the Haddock comment can make you 
think so. pwrapper allows you to talk *CGI* over a TCP port, but I have 
no idea why anyone would like to do that.


Here is a scenerio. I want a basic web application: someone makes a 
request, and my program computes a response.


* For one reason or another, I settle with CGI.

* The program is huge and slow to load. (Let's say it statically links 
in the whole GHC API and therefore is basically GHC itself. :) ) It 
would suck to re-load this program at every request.


* Or, the program performs work that requires more file-system privilege 
than the admin of the web server grants. You know, a good admin sets up 
a web server and all CGI scripts to run with nobody's privilege.


* Or, nevermind performance or privilege. I am a cheapo, and I use a 
cheapo hosting provider, which only provides me with 3MB of storage. My 
program weighs 17MB (recall that it links in the whole GHC :) ).


Here is a solution. The program runs as a daemon and never quits; it can 
run somewhere with sufficient privilege and storage. It talks CGI over 
TCP. At the web server, which is super-slow, super-paranoid, and 
super-cheapo, the CGI script is a lightweight C program that redirects 
everything over TCP to my daemon.


(Here is a counter-solution. The program still runs as a daemon 
somewhere, but it talks my own protocol over TCP. The CGI script is a 
lightweight C program that parses CGI into my own protocol. Besides 
having to design my own protocol carefully, here is a problem: C is a 
great language for writing parsers that are incomplete, inconsistent, 
and insecure. :) )

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


Re: [Haskell-cafe] Re: Very fast loops. Now!

2007-02-12 Thread David Roundy
On Mon, Feb 12, 2007 at 02:25:21PM -0800, Bryan O'Sullivan wrote:
 David Roundy wrote:
 I'm rather curious (if you're sill interested) how this'll be affected by
 the removal of the division from the inner loop. e.g.
 
 go :: Double - Double - Int - IO ()
 go !x !y !i
 | i == 10 = printf %.6f\n (x+y)
 | otherwise   = go (x*y*(1.0/3)) (x*9) (i+1)
 
 
 for (; i10; i++) {
 x = x*y*(1.0/3.0);
 y = x*9.0;
 }
 
 GCC will do the transformation itself if you use -ffast-math.  It 
 requires the flag as the results aren't exactly numerically equivalent.

Ah, okay.  Never mind, then.
-- 
David Roundy
Department of Physics
Oregon State University
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Foldr tutorial, Inspired by Getting a Fix from a Fold

2007-02-12 Thread Lennart Augustsson

I thought solution one was missing the ~ ?

On Feb 12, 2007, at 22:07 , [EMAIL PROTECTED] wrote:


Bernie Pope wrote:

Lennart Augustsson wrote:

Sure, but we also have

para f e xs = snd $ foldr (\ x ~(xs, y) - (x:xs, f x xs y)) ([],  
e) xs

Nice one.


Nice one is an euphemism, it's exactly solution one :)

Regards,
apfelmus

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


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


[Haskell-cafe] Summer of Code

2007-02-12 Thread Bryan Burgers

Hello,

Yes, I realize it's mid-February right now and the summer is still
months away, but it's probably not too early to think about the
future.

I am wondering if there are any Summer of Code projects that I would
be able to do for the Haskell community. I will be graduating from my
undergrad program this semester and am hoping to go on to graduate
school in the fall, and I think a good Haskell project would be the
perfect way to spend my transitional summer.

I looked at 
http://hackage.haskell.org/trac/summer-of-code/query?status=newstatus=assignedstatus=reopenedgroup=topictype=proposed-projectorder=priority
to see if there was anything that people already had in mind, but that
page looks old and unkempt (judging by the abundance of
advertisements) so I am not sure which of those are still available or
needed.

So, are there any projects that will need a student for the summer? If
this is not the place to ask, where should I be asking?

Bryan Burgers
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] IO is not a monad

2007-02-12 Thread Lennart Augustsson

No, I can't say off hand if seq-hnf would keep eta valid, either.
Neither do I know how to implement seq-hnf efficiently. :)

As far as eta for other types, yes, I'll take it if I can get it's  
easily.

But I'm also pretty happy with encoding all the other data types within
the lambda calculus (which was how Haskell behaved before seq).

-- Lennart

On Feb 12, 2007, at 22:05 , Claus Reinke wrote:


Adding seq ruins eta reduction.  For normal order lambda calculus
we have '\x.f x = f' (x not free in f).  If we add seq this is no  
longer true.


isn't that a problem of seq (and evaluation in Haskell generally)  
not being strict enough (ie, forcing evaluation only to weak head  
normal form rather than to head normal form)?


for instance:

   seq (\x-_|_ x) () = () =/= _|_ = seq _|_ ()

but (assuming a variant, seq-hnf, forcing to hnf instead):
   seq-hnf (\x- _|_ x ) () = _|_ = seq-hnf _|_ ()

I don't have my phone book here, but didn't Barendregt have a  
discussion
of what kind of normal form would be an appropriate choice for the  
meaning
of lambda terms, with hnf being good and whnf or nf being bad?  
reduction
to whnf is a pragmatic choice, with a long history, and its own  
calculus, which is not quite the ordinary lambda calculus.


but it's been ages since I learned these things, so I might be  
misremembering.


Claus


I'm a fan of eta, it makes reasoning easier.  It also means
the compiler can do more transformations.


I also like eta conversion, as well as its variations for non- 
function types. what they have in common is that the expanded form  
provides syntactic/structural evidence for properties that are only  
semantically present in the reduced form. for instance, if we add  
non-functions to the calculus, eta has to be
constrained with type information for f - as the expanded form  
promises that we have a function, holding more information than the  
reduced form.


variations of eta for non-function types, this allows us to make  
functions/
contexts less strict (the kind of borrowing information from the  
future so often needed in cyclic programming, or in dealing with  
other potentially infinite structures):


   lazy_id_pair x = (fst x,snd x)-- lazy_id_pair _|_ = (_|_,_|_)

vs

   strict_id_pair (a,b) = (a,b)-- strict_id_pair _|_ = _|_

at the expense of not having laws like:
   x = (fst x,snd x)-- not true in general, even if we know  
that x::(a,b)


   x = x = return-- not true in general, even if x :: Monad m  
= m a


   x = \y- x y-- not true in general, even if x :: a - b

we still have the inequalities, though - the expanded form being more
defined than the reduced form.

   x :: t ]= (expand-at-t x) :: t-- eta conversion at type t

so compilers could use eta-expansion, but not eta-reduction (not  
without
an approximate analysis of an undecidable property). do you happen  
to have an example in mind where eta-reduction would be beneficial  
as a compiler transformation, but analysis (to demonstrate that the  
expanded functional expression terminates successfully) impractical?


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


Re: [Haskell-cafe] Summer of Code

2007-02-12 Thread Donald Bruce Stewart
bryan.burgers:
 Hello,
 
 Yes, I realize it's mid-February right now and the summer is still
 months away, but it's probably not too early to think about the
 future.
 
 I am wondering if there are any Summer of Code projects that I would
 be able to do for the Haskell community. I will be graduating from my
 undergrad program this semester and am hoping to go on to graduate
 school in the fall, and I think a good Haskell project would be the
 perfect way to spend my transitional summer.
 
 So, are there any projects that will need a student for the summer? If
 this is not the place to ask, where should I be asking?
 

Here's some general advice for those considering applying for 
the Summer of Code Haskell projects. We haven't prepared a list yet of
desirable features, but going on last year's successful applicants, the
following qualities will be required:

 1. The project should have:
* clear benefit to the Haskell community
* there will be an emphasis on new libraries
  and on new development tools.

We really prefer people work on things that the community needs:
libraries and development tools. Some suggestions would be the http
lib, a binary/bitstream parsec, or a light web framework (that works
out of the box), ghc-api integration with emacs/vim.

 2. The applicant should have:

* demonstrated experience with Haskell programming
* demonstrated experience working alone, (e.g. open source
  experience is a great asset)

With over 100 applicants, and 9 positions available, competition is
tough. You can stand out by contributing to projects *now* so that you
gain experience with the current best Haskell development practices, and
get some guidance from the open source hackers in the community about
how to work efficiently and with community consensus.

Start working now on your own library or app, get it in darcs, publish
it, upload it to hackage, and when summer comes around, you'll have
massively increased your changes of being selected.

-- Don
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Even better Eratosthenes sieve and lucky numbers

2007-02-12 Thread oleg

We further simplify the previously posted genuine sieve algorithm and
generalize it to the finding of lucky numbers. 

We observe that we only need to store marks _signifying_ the integers,
but never the integers themselves. Thus we arrive at the algorithm
that is distinguished from all previously posted by:
(i) doing no operations on composite numbers
(ii) using neither multiplication nor division nor the
remainder operation
(iii) using neither general addition nor the comparison.

The algorithm only relies on the successor, predecessor and zero
comparison. The predecessor can be easily eliminated. Thus the
algorithm can be used with Church and Peano numerals, or members of
Elliptic rings, where zero comparison and successor take constant
time but other arithmetic operations are more involved.

 -- repl_every_n n l replaces every (n+1)-th element in a list (_:l)
 -- with False
 repl_every_n :: Int - [Bool] - [Bool]
 repl_every_n n l = repl_every_n' n l
  where repl_every_n' 0 (_:t) = False: repl_every_n n t
repl_every_n' i (h:t) = h: repl_every_n' (pred i) t

 primes = 2:(loop 3 (repeat True))
  where loop n (False:t) = loop (succ (succ n)) t
loop n (_:t)  = n:(loop (succ (succ n)) (repl_every_n (pred n) t))

 main = putStrLn $ Last 10 primes less than 1:  ++ 
show (take 10 $ reverse  $ takeWhile ( 1) primes)

Last 10 primes less than 1: 
 [9973,9967,9949,9941,9931,9929,9923,9907,9901,9887]

The algorithm easily generalizes to lucky numbers
http://mathworld.wolfram.com/LuckyNumber.html
http://www.research.att.com/~njas/sequences/A000959

 -- Consider the series of odd numbers starting with k=1; the k-th number
 -- is 2k-1. 
 -- If we start the elimination from the very beginning of the series (k=1),
 -- we start with the phase (2k-2) and eliminate with the step 2k-2.
 -- If we start at the number k+1, the phase becomes (2k-2-k) = (k-2).
 -- Thus the starting phase gets incremented by 1 as we move up the series.
 -- However, already eliminated numbers don't count, so as we skip
 -- over eliminated numbers, we increment the phase by 2
 lucky = 1:(loop 3 0 (repeat True))
  where loop n i (False:t) = loop (succ (succ n)) (succ (succ i)) t
loop n i (_:t)  = n:(loop (succ (succ n)) (succ i)
 (repl_every_np i (pred n) t))

 -- repl_every_np i n eliminates (marks as False) every (n+1)-th number
 -- starting with the phase i.
 -- Already eliminated numbers don't count.
 repl_every_np :: Int - Int - [Bool] - [Bool]
 repl_every_np i n (False:t) = False: repl_every_np i n t
 repl_every_np 0 n (_:t) = False: repl_every_np n n t
 repl_every_np i n (_:t) = True:  repl_every_np (pred i) n t

*Main take 10 lucky
[1,3,7,9,13,15,21,25,31,33]
*Main takeWhile (100) lucky
[1,3,7,9,13,15,21,25,31,33,37,43,49,51,63,67,69,73,75,79,87,93,99]

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


[Haskell-cafe] ANNOUNCE: urlcheck 0.1, (smp) parallel link checker

2007-02-12 Thread Donald Bruce Stewart
This little tool has been kicking around on my harddrive for a month or
two now, so time to release!

I'm pleased to announce the first release of urlcheck, an parallel link
checker, written in Haskell.

Frustrated with the resources and time consumed by 'linkchecker', when
preparing the weekly news, I coded up a lightweight, smp-capable
replacement in Haskell.  urlcheck pings urls found in the input file,
checking they aren't 404s. 

It uses Haskell threads to run queries concurrently, and can
transparently utilise multiple cores if you have them.

Usage:

$ urlcheck urlcheck.html
Found 0 broken links. Checked 10 links (10 unique) in 1 file.
Search time: 5 secs

Get it from Hackage!

http://hackage.haskell.org/cgi-bin/hackage-scripts/package/urlcheck-0.1 

-- Don 

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


Re: Re[2]: [Haskell-cafe] Re: Optimization fun

2007-02-12 Thread Matthew Brecknell
Lennart Augustsson said:
 Many architectures gives both the quotient and remainder when you use
 the division instruction, so divMod (quotRem) shouldn't cost more  
 than a div or mod.  But if the code generator takes advantage of that
 is another matter.

You're quite right.

Bulat Ziganshin said:
 qoutRem# is primitive operation in GHC

I can see quotRemInteger# and divModInteger#, as well as quotInt#,
remInt#, divInt# and modInt#, but not quotRemInt# nor divModInt#. For
example:

$ ghc --show-iface Num.hi

divModInt :: GHC.Base.Int - GHC.Base.Int - (GHC.Base.Int,
GHC.Base.Int)
  {- Arity: 2 HasNoCafRefs Strictness: U(L)U(L)m
 Unfolding:
 (\ x :: GHC.Base.Int y :: GHC.Base.Int -
  case @ (GHC.Base.Int, GHC.Base.Int) x of wild { I# ds -
  case @ (GHC.Base.Int, GHC.Base.Int) y of wild1 { I# ds1 -
  (GHC.Base.I# (GHC.Base.divInt#{1} ds ds1),
   GHC.Base.I# (GHC.Base.modInt#{1} ds ds1)) } }) -}

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