Re: [Haskell-cafe] What is the role of $!?

2007-11-18 Thread Andrew Coppin

PR Stanley wrote:

Hi
okay, so $! is a bit like $ i.e. the equivalent of putting parentheses 
around the righthand expression. I'm still not sure of the difference 
between $ and $!. Maybe it's because I don't understand the meaning of 
strict application. While we're on the subject, what's meant by 
Haskell being a non-strict language?

Cheers
Paul


It simply means in Haskell, if you call a function, that function is not 
executed until you try to do something with the result.


f $ x + y is like f (x + y). The value of x + y will only actually 
be calculated if f tries to examine its value. For example,


 f1 x = 7
 f2 x = if x == 0 then 0 else 1

The f1 function ignores x and always returns 7. If you did f1 $ x 
+ y, then x + y would never ever be calculated at all.


However, f2 looks at x to see if it's 0. So if you do f2 $ x + y, 
the x + y part will be calculated.


f $! x + y is just like f $ x + y, except that x + y will be 
calculated *before* f is called - regardless of whether f does 
anything with this data.


The usual reason for doing this is to avoid large unevaluated 
expressions accumulating inside a program loop - e.g., if you were 
calculating a total, you probably want the total variable to actually 
contain the total rather than just a big expression like 1 + 2 + 3 + 
..., so you could use $! to force the total to actually be calculated 
before starting the next loop [which will be a recursive function call].


Make any sense?

PS. There is a technical distinction between the terms lazy and 
non-strict, and also the opposite terms eger and strict. I 
couldn't tell you what that is.


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


Re: [Haskell-cafe] Stream fusion for Hackage

2007-11-18 Thread Tom Schrijvers

On Sat, 17 Nov 2007, Don Stewart wrote:


Just a quick announce: the stream fusion library for lists,
that Duncan Coutts, Roman Leshchinskiy and I worked on earlier this year
is now available on Hackage as a standalone package:

   
http://hackage.haskell.org/cgi-bin/hackage-scripts/package/stream-fusion-0.1.1

As described in the recent paper:

   Stream Fusion: From Lists to Streams to Nothing at All
   Duncan Coutts, Roman Leshchinskiy and Don Stewart. ICFP 2007

This is a drop-in replacement for Data.List.


Will it eventually replace Data.List in GHC?

Tom

--
Tom Schrijvers

Department of Computer Science
K.U. Leuven
Celestijnenlaan 200A
B-3001 Heverlee
Belgium

tel: +32 16 327544
e-mail: [EMAIL PROTECTED]
url: http://www.cs.kuleuven.be/~toms/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Stream fusion for Hackage

2007-11-18 Thread Andrew Coppin

Don Stewart wrote:
Just a quick announce: the stream fusion library for lists, 
that Duncan Coutts, Roman Leshchinskiy and I worked on earlier this year

is now available on Hackage as a standalone package:


http://hackage.haskell.org/cgi-bin/hackage-scripts/package/stream-fusion-0.1.1

As described in the recent paper:

Stream Fusion: From Lists to Streams to Nothing at All
Duncan Coutts, Roman Leshchinskiy and Don Stewart. ICFP 2007

This is a drop-in replacement for Data.List.
  


So let me get this straight... If I take a program that does lots of 
list processing, and import this module instead of Data.List, the 
program will magically go faster?


Sounds good to me! :-D

I wonder if this will make my Burrows-Weeler Transform program go any 
faster? That's 100% list processing...


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


Re: [Haskell-cafe] Letting the darcs test fail, if QuickCheck tests fail

2007-11-18 Thread Henning Thielemann

On Tue, 30 Oct 2007, David Roundy wrote:

 On Tue, Oct 30, 2007 at 05:24:21PM +0100, Henning Thielemann wrote:
  When following the description on
   
  http://www.haskell.org/haskellwiki/How_to_write_a_Haskell_program#Add_some_automated_testing:_QuickCheck
then darcs will run the QuickCheck tests on each 'darcs record', but the
  new patch is also accepted by darcs if one of the tests fail. What is the
  most simple way to let 'darcs record' fail, when a QuickCheck test fails?

 You can do this with QuickCheck 2 using quickCheck', but I don't know how
 to do this with QuickCheck 1.  xmonad uses a function mytests, which I
 guess is pretty much copied from the code of QuickCheck 1, with tracking of
 errors added in.  It's ugly, but it's only a few dozen lines.

 Another option would be to grep the output of the test suite to look for
 failure.

I didn't want to introduce the dependency on QuickCheck2 just for
quickCheck', so I went for the 'grep' solution. I also added your hints to
  
http://www.haskell.org/haskellwiki/How_to_write_a_Haskell_program#Running_the_test_suite_from_darcs

Admittedly, the grep solution will be certainly restricted to Unix. Even
more I became aware, that grepping for 'Falsifiable' only catches
unsatisfied tests, but if a test fails with 'error' this slips through.
I could add some handling for this case, but I feel that I'm missing
something, again.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] New demo/test program for Yhc Javascript backend

2007-11-18 Thread Bit Connor
This is very cool!
I will definitely be playing with this.

Safari 3.0.2 for windows gives an error though:

  Maximum call stack size exceeded.
  http://darcs.haskell.org/yhc/web/jsdemos/HsWTKDemo.html Line: 87

Sometimes it gives the same error but instead of line 87 with line
314, and other times line 224 or 422

Are you aware of this issue?

Thanks

On Nov 17, 2007 8:32 AM, Dimitry Golubovsky [EMAIL PROTECTED] wrote:
 Hi,

 For those of you who are interested in using Haskell in client-side
 web application programming:

 I have added a new demo/test program to this Wiki page (Does it leak?):

 http://haskell.org/haskellwiki/Yhc/Javascript

 This demo program shows some progress made since the first
 announcement of Yhc Javascript backend (Core to Javascript converter)
 was made about a year ago. Please test the demo for functionality and
 memory leaks in various browsers. Your feedback is appreciated.

 The demo program is self-contained (does not require any Haskell
 libraries beyond those included with Yhc). There is a darcs repo:
 http://www.golubovsky.org/repos/wsptest/ from which this demo program
 along with Makefile can be obtained if anybody wants to play with the
 code.

 Thanks.

 --
 Dimitry Golubovsky

 Anywhere on the Web
 ___
 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] New demo/test program for Yhc Javascript backend

2007-11-18 Thread Dimitry Golubovsky
Bit,

On Nov 18, 2007 8:41 AM, Bit Connor [EMAIL PROTECTED] wrote:

 Safari 3.0.2 for windows gives an error though:

   Maximum call stack size exceeded.
   http://darcs.haskell.org/yhc/web/jsdemos/HsWTKDemo.html Line: 87

This  is in fact a huge progress for Safari ;) Year ago, Safari on Mac
gave some weird error message Type Error line 1.

See http://osdir.com/ml/lang.haskell.yhc/2006-11/msg00033.html

The problem is, I am not sure how it enumerates lines.

Lines around 87 (ran with pr -n):

   83   var consStr = function (s) {
   84 if (s.length == 0) {
   85   return new HSEOL ();
   86 } else {
   87   var hdc = mkChar (s.charCodeAt (0));
   88   return new HSCons (hdc, s.length  1 ? s.substring (1) :
consStr ());
   89 };
   90   };

Nothing suspicious because mkChar is a wrapper around the Number constructor.

Line 314:

  312   function NEG_D(a) {
  313 return -(exprEval(a));
  314   }

and so on.


 Sometimes it gives the same error but instead of line 87 with line
 314, and other times line 224 or 422

But does it at least display the widgets? Or do these errors appear as
you press buttons/type anything?


 Are you aware of this issue?

Now I am ;) But to me not being an expert in Safari, these error
messages do little help (or if at least I knew what actual lines they
meant)...

Thanks.

-- 
Dimitry Golubovsky

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


Re: [Haskell-cafe] What is the role of $!?

2007-11-18 Thread Paul Johnson

Andrew Coppin wrote:


PS. There is a technical distinction between the terms lazy and 
non-strict, and also the opposite terms eger and strict. I 
couldn't tell you what that is.
As I understand it, the distinction is between the mathematical term 
non-strict and the implementation method of lazy.  Non-strict 
means that reduction (the mathematical term for evaluation) proceeds 
from the outside in, so if I have (a+(b*c)) then first you reduce the 
+, then you reduce the inner (b*c).  Strict languages work the other 
way around, starting with the innermost brackets and working outwards.


This matters to the semantics because if you have an expression that 
evaluates to bottom (i.e. an error, exception or endless loop) then 
any language that starts at the inside and works outwards will always 
find that bottom value, and hence the bottom will propogate outwards.  
However if you start from the outside and work in then some of the 
sub-expressions are eliminated by the outer reductions, so they don't 
get evaluated and you don't get bottom.


Lazy evaluation, on the other hand, means only evaluating an expression 
when its results are needed (note the shift from reduction to 
evaluation).  So when the evaluation engine sees an expression it 
builds a thunk data structure containing whatever values are needed to 
evaluate the expression, plus a pointer to the expression itself.  When 
the result is actually needed the evaluation engine calls the expression 
and then replaces the thunk with the result for future reference.


Obviously there is a strong correspondance between a thunk and a 
partly-evaluated expression.  Hence in most cases the terms lazy and 
non-strict are synonyms.  But not quite.  For instance you could 
imagine an evaluation engine on highly parallel hardware that fires off 
sub-expression evaluation eagerly, but then throws away results that are 
not needed.


In practice Haskell is not a purely lazy language: for instance pattern 
matching is usually strict (so trying a pattern match forces evaluation 
to happen at least far enough to accept or reject the match).  The 
optimiser also looks for cases where sub-expressions are *always* 
required by the outer expression, and converts those into eager 
evaluation.  It can do this because the semantics (in terms of bottom) 
don't change.  Programmers can also use the seq primitive to force an 
expression to evaluate regardless of whether the result will ever be 
used.  $! is defined in terms of seq.


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


Re: [Haskell-cafe] What is the role of $!?

2007-11-18 Thread David Menendez
On Nov 18, 2007 9:23 AM, Paul Johnson [EMAIL PROTECTED] wrote:
 Obviously there is a strong correspondance between a thunk and a
 partly-evaluated expression.  Hence in most cases the terms lazy and
 non-strict are synonyms.  But not quite.  For instance you could
 imagine an evaluation engine on highly parallel hardware that fires off
 sub-expression evaluation eagerly, but then throws away results that are
 not needed.

I've mostly seen lazy evaluation used for the strategy where thunks
are only evaluated once.

Consider the function f x = g x x and the code f (a + b). Because
Haskell is lazy, it only evaluates a + b once, even though f (a +
b) reduces to g (a + b) (a + b).

In Haskell, the only difference between f (a + b) and g (a + b) (a
+ b) is efficiency, but there are languages that have non-strict
functions and side-effects. In Algol, IIRC, you could define function
parameters to be call-by-name. A function call like f(inc(y)) would
not evaluate inc(y) until f used its parameter, but it would
evaluate it again each time.

The difference between call-by-name and laziness (aka call-by-need) is
analogous to the difference between these monadic functions:

f1 m = m = \x - g x x
f2 m = m = \x1 - m = \x2 - g x1 x2

-- 
Dave Menendez [EMAIL PROTECTED]
http://www.eyrie.org/~zednenem/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] What is the role of $!?

2007-11-18 Thread Lauri Alanko
Please note that if you're using GHC, bang patterns are often much
more convenient than $! or seq when you want to enforce strictness:

http://www.haskell.org/ghc/docs/latest/html/users_guide/bang-patterns.html


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


[Haskell-cafe] Re: Knot tying vs monads

2007-11-18 Thread apfelmus

Brent Yorgey wrote:

but isn't there a short text that describes in detail why foldl' is
different from foldl and why foldr is better in many cases? I thought
this faq would have been cached already :)



Perhaps you're thinking of http://haskell.org/haskellwiki/Stack_overflow ?


Ah, that looks better, although it's a bit messy for my taste. I've 
scribbled a hopefully gentler explanation at 
http://en.wikibooks.org/wiki/Haskell/Performance_Introduction .



Regards,
apfelmus

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


[Haskell-cafe] Re: What is the role of $!?

2007-11-18 Thread apfelmus

Paul Johnson wrote:

Andrew Coppin wrote:


PS. There is a technical distinction between the terms lazy and 
non-strict, and also the opposite terms eger and strict. I 
couldn't tell you what that is.


As I understand it, the distinction is between the mathematical term 
non-strict and the implementation method of lazy.  Non-strict 
means that reduction (the mathematical term for evaluation) proceeds 
from the outside in, so if I have (a+(b*c)) then first you reduce the 
+, then you reduce the inner (b*c).  Strict languages work the other 
way around, starting with the innermost brackets and working outwards.

[...]


Almost right, but strict and non-strict aren't tied to an operational 
semantics. In other words, you can talk about _|_ and strictness without 
knowing how to evaluate your expressions at all. See also


  http://en.wikibooks.org/wiki/Haskell/Denotational_semantics .

For more on the details of lazy evaluation (which actually does work 
outside in), there's the incomplete


  http://en.wikibooks.org/wiki/Haskell/Graph_reduction .

Of course, strict and eager as well as non-strict and lazy have pretty 
much the same effect and can be used synonymously, but they're different 
things nonetheless.



Regards,
apfelmus

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


[Haskell-cafe] Properties of monads

2007-11-18 Thread Radosław Grzanka
Hello,
  I am writing some toys programs to learn and try to apply Monads
properties (without success, I must say). Although I spent half a day
on this code:

http://hpaste.org/3957

I couldn't simplify (shorten) getStrip function. After reading Doing
it with class (
http://www.haskell.org/all_about_monads/html/class.html ) I had an
impression that I could collapse cases using some Monads properties.
But maybe I misunderstood something.

Can anyone look at it and give me a pointers?? (I don't mind if the
code becomes unreadable a bit.)

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


Re: [Haskell-cafe] Properties of monads

2007-11-18 Thread Radosław Grzanka
Hi Benja,

 You can find MaybeT here:

 http://www.haskell.org/haskellwiki/New_monads/MaybeT

Thank you, that you spent some time figuring this out. This is exacly
what I have expected. (This print was debug leftovers).

Now I will try to understand how exacly this works.

My big thanks to you again,
 Radek.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Properties of monads

2007-11-18 Thread Benja Fallenstein
Hi Radosław,

You should be able to write this with MaybeT as follows:

getStrip :: IO ( Maybe String )
getStrip = runMaybeT $ do
pageContent - liftIO $ downloadFile mainPageAddress
let x = patternForStrip pageContent
print x
z - x
liftIO $ downloadFile $ mainPageAddress ++ z

If you can do without the 'print', you should be able to write it as:

getStrip :: IO ( Maybe String )
getStrip = runMaybeT $ do
pageContent - liftIO $ downloadFile mainPageAddress
z - patternForStrip pageContent
liftIO $ downloadFile $ mainPageAddress ++ z

You can find MaybeT here:

http://www.haskell.org/haskellwiki/New_monads/MaybeT

Best,
- Benja

On 11/18/07, Radosław Grzanka [EMAIL PROTECTED] wrote:
 Hello,
   I am writing some toys programs to learn and try to apply Monads
 properties (without success, I must say). Although I spent half a day
 on this code:

 http://hpaste.org/3957

 I couldn't simplify (shorten) getStrip function. After reading Doing
 it with class (
 http://www.haskell.org/all_about_monads/html/class.html ) I had an
 impression that I could collapse cases using some Monads properties.
 But maybe I misunderstood something.

 Can anyone look at it and give me a pointers?? (I don't mind if the
 code becomes unreadable a bit.)

 Thank you,
   Radek.
 ___
 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] What is the role of $!?

2007-11-18 Thread Andrew Coppin

Lauri Alanko wrote:

Please note that if you're using GHC, bang patterns are often much
more convenient than $! or seq when you want to enforce strictness:

http://www.haskell.org/ghc/docs/latest/html/users_guide/bang-patterns.html
  


Wait, so...

 f x = x + 1; f $! (a + b)

and

 f !x = x + 1; f (a + b)

mean the same thing?

Well, you learn something new every day... (I guess wanting a function's 
arguments to evaluate before the rest of that function is quite a common 
thing to want. Neat!)


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


Re: [Haskell-cafe] Properties of monads

2007-11-18 Thread Benja Fallenstein
On 11/18/07, Benja Fallenstein [EMAIL PROTECTED] wrote:
 Hi Radosław,

 You should be able to write this with MaybeT as follows:

Correction, sorry. The code in my original mail doesn't take care of
converting the 'Maybe's returned by the functions you're calling into
'MaybeT's.

The following should work, but is a little annoying:

getStrip :: IO ( Maybe String )
getStrip = runMaybeT $ do
pageContent - MaybeT $ downloadFile mainPageAddress
z - MaybeT $ return $ patternForStrip pageContent
MaybeT $ downloadFile $ mainPageAddress ++ z

Something like the following might feel cleaner, though:

maybeT :: Maybe a - MaybeT m a
maybeT = MaybeT . return

downloadFile :: String - MaybeT IO String
downloadFile s = maybeT (parseURI s) = liftIO . httpGet

getStrip :: MaybeT IO String
getStrip = do
pageContent - downloadFile mainPageAddress
z - maybeT $ patternForStrip pageContent
downloadFile $ mainPageAddress ++ z

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


Re[2]: [Haskell-cafe] What is the role of $!?

2007-11-18 Thread Bulat Ziganshin
Hello Andrew,

Sunday, November 18, 2007, 10:04:15 PM, you wrote:

 Wait, so...

f x = ...
g = f $! x

 and

f !x = ...
g = f x

 mean the same thing?

in both cases, x is evaluated before evaluating body of x. but of
course, this happens only at the moment when value of (f x) itself is
required


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


Re: [Haskell-cafe] Stream fusion for Hackage

2007-11-18 Thread Don Stewart
Tom.Schrijvers:
 On Sat, 17 Nov 2007, Don Stewart wrote:
 
 Just a quick announce: the stream fusion library for lists,
 that Duncan Coutts, Roman Leshchinskiy and I worked on earlier this year
 is now available on Hackage as a standalone package:
 

  http://hackage.haskell.org/cgi-bin/hackage-scripts/package/stream-fusion-0.1.1
 
 As described in the recent paper:
 
Stream Fusion: From Lists to Streams to Nothing at All
Duncan Coutts, Roman Leshchinskiy and Don Stewart. ICFP 2007
 
 This is a drop-in replacement for Data.List.
 
 Will it eventually replace Data.List in GHC?

That is the plan, yep.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Network.HTTP problem

2007-11-18 Thread Radosław Grzanka
Hello again Bjorn,

 This is now fixed and a new release with the fix is available from
 http://hackage.haskell.org/cgi-bin/hackage-scripts/package/HTTP-3001.0.1

You have left debug flag on in the library code.

Thanks,
  Radek.


-- 
Codeside: http://codeside.org/
Przedszkole Miejskie nr 86 w Lodzi: http://www.pm86.pl/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Network.HTTP problem

2007-11-18 Thread Bjorn Bringert

On Nov 18, 2007, at 22:08 , Radosław Grzanka wrote:


Hello again Bjorn,


This is now fixed and a new release with the fix is available from
http://hackage.haskell.org/cgi-bin/hackage-scripts/package/ 
HTTP-3001.0.1


You have left debug flag on in the library code.

Thanks,
  Radek.


Dammit. I forgot that cabal sdist of course uses the code in the  
current directory, not what's recorded in darcs. Silly me. 3001.0.2  
fixes this, http://hackage.haskell.org/cgi-bin/hackage-scripts/ 
package/HTTP-3001.0.2


Thanks!

/Björn



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


[Haskell-cafe] Performance problems with parallelizing QuickCheck using channels (Control.Concurrent.Chan)

2007-11-18 Thread Gwern Branwen
(My previous email showed up as mangled in
http://www.haskell.org/pipermail/haskell-cafe/2007-November/034717.html;
I think the PGP signature was the problem; I removed it and sent it
again, but it was put into moderation for size, and hasn't been
released yet - so I'm sending this a third time but I'm removing
attachments so it'll be under the annoying 20k size limit)


So I've been trying to get my QuickCheck tests to run in parallel. I
did take a look at Don's Parallel QuickCheck library
http://www.cse.unsw.edu.au/~dons/pqc.html, but I didn't like how
much code it had in it and I figured it'd be a good exercise to try to
do myself.

After quite a lot of help from the good folk of #haskell, I eventually
came up with this:
  module Pcheck (parTest, parCheck) where

  import Control.Monad (replicateM_, liftM)
  import Control.Concurrent.Chan (newChan, writeChan, getChanContents)
  import Control.Concurrent (forkIO)
  import Test.QuickCheck (quickCheck', Testable())

  -- | Takes a list of functions using parCheck, and returns True iff all return
  -- True. Evaluates them in parallel.
  parTest :: [IO Bool] - IO Bool
  parTest = andTest . parList
  where andTest :: IO [Bool] - IO Bool
andTest = liftM and

  {- | Test in parallel. Forks off a QuickCheck 'n' times; QuickCheck
tests using
   the proposition 't'. Returns True if all tests were passed, else
   False. Should be run with parallelizing options like with +RTS -N4
-RTS etc. -}
  parCheck :: (Testable prop) = prop - Int - IO Bool
  parCheck t n = do chan - newChan
replicateM_ n $ forkIO $ (writeChan chan) =
(quickCheck' t)
liftM (and . take n) $ getChanContents chan

  -- | Takes a list of functions (presumably using parCheck) and
evaluates all in parallel.
  parList :: [IO a] - IO [a]
  parList fs = do chan - newChan
  mapM_ (\m - forkIO $ m = writeChan chan) fs
  liftM (take n) $ getChanContents chan
  where n = length fs

I liked how simple the Channels library
http://haskell.org/ghc/docs/latest/html/libraries/base-3.0.0.0/Control-Concurrent-Chan.html
seemed to be; I could just pass the channel as an argument and have
every forkIO'd test simply chuck its Boolean result into it when done
- which seem'd much simpler than using MVars and the other techniques
for returning stuff from forkIO threads.

And so it compiles, it runs tests correctly, and so on. But the
problem is that it does so slowly. I have another module of equations
about nuclear bombs called nuke.hs, which has a number of QuickCheck
properties defined. Here's what happens when main is defined as
'parTest [the various tests..]':

 ./nuke +RTS -N7 -sstderr -RTS 40.57s user 46.55s system 116% cpu 1:14.61 total
 ./nuke +RTS -N6 -sstderr -RTS 40.72s user 47.66s system 117% cpu 1:15.50 total
 ./nuke +RTS -N5 -sstderr -RTS 42.33s user 49.08s system 116% cpu 1:18.67 total
 ./nuke +RTS -N4 -sstderr -RTS 43.71s user 48.41s system 117% cpu 1:18.48 total
 ./nuke +RTS -N3 -sstderr -RTS 41.51s user 48.25s system 114% cpu 1:18.10 total
 ./nuke +RTS -N2 -sstderr -RTS 42.28s user 47.18s system 115% cpu 1:17.39 total
 ./nuke +RTS -N1 -sstderr -RTS 27.87s user 18.40s system 99% cpu 46.498 total

(From http://hpaste.org/3886#a6; compiled as =ghc -v --make
-threaded -O2 ./nuke.hs.)

For some reason, running the parallel tests with a single thread is
faster than running with 4 threads (I have a quad-core Intel
processor)? I find this counter-intuitive to say the least. the par*
functions are indeed operating in parallel, as evidenced by it using
more than 100% CPU time, or, running on multiple cores, and all the
tests are passed as True in both -N1 and -N[2-7] versions, so -N1
can't be bailing out early due to and's laziness, and in general
everything seems to be written correctly.

I am perplexed by this. Is Chan simply a very inefficient way of
parallelizing things? Is it not as parallel as I think? Or am I
missing something else entirely?

--
gwern
.45 GIGN jya. wire ISI SADCC JPL embassy Recon World
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Performance problems with parallelizing QuickCheck using channels (Control.Concurrent.Chan)

2007-11-18 Thread Don Stewart
gwern0:
 (My previous email showed up as mangled in
 http://www.haskell.org/pipermail/haskell-cafe/2007-November/034717.html;
 I think the PGP signature was the problem; I removed it and sent it
 again, but it was put into moderation for size, and hasn't been
 released yet - so I'm sending this a third time but I'm removing
 attachments so it'll be under the annoying 20k size limit)
 
 
 So I've been trying to get my QuickCheck tests to run in parallel. I
 did take a look at Don's Parallel QuickCheck library
 http://www.cse.unsw.edu.au/~dons/pqc.html, but I didn't like how
 much code it had in it and I figured it'd be a good exercise to try to
 do myself.
 

Did you compare it against the multicore performance of the original
pqc? (Which I've found fairly good). The trick is to ensure enough
work is done per thread, so you don't get overwhelmed by communication.

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


[Haskell-cafe] An interesting monad: Prompt

2007-11-18 Thread Ryan Ingram
(This message is a literate haskell file.  Code for the Prompt monad is
preceded by ; code for my examples is preceded by ] and isn't complete,
but intended for illustration.)

I've been trying to implement a few rules-driven board/card games in Haskell
and I always run into the ugly problem of how do I get user input?

The usual technique is to embed the game in the IO Monad:

] type Game = IO
] -- or
] type Game = StateT GameState IO

The problem with this approach is that now arbitrary IO computations are
expressible as part of a game action, which makes it much harder to
implement
things like replay, undo, and especially testing!

The goal was to be able to write code like this:

] takeTurn :: Player - Game ()
] takeTurn player = do
] piece  - action (ChoosePiece player)
] attack - action (ChooseAttack player piece)
] bonusTurn - executeAttack piece attack
] when bonusTurn $ takeTurn player

but be able to script the code for testing, allow undo, automatically
be able to save replays, etc.

While thinking about this problem earlier this week, I came up with the
following solution:

 {-# OPTIONS_GHC -fglasgow-exts -fallow-undecidable-instances  #-}
 -- undecidable instances is only needed for the MonadTrans instance below

 module Prompt where
 import Control.Monad.Trans
 import Control.Monad.Identity

 class Monad m = MonadPrompt p m | m - p where
prompt :: p a - m a

prompt is an action that takes a prompt type and gives you a result.

A simple example:
] prompt [1,3,5] :: MonadPrompt [] m = m Int

This prompt would ask for someone to pick a value from the list and return
it.
This would be somewhat useful on its own; you could implement a choose
function that picked randomly from a list of options and gave
non-deterministic (or even exhaustive) testing, but on its own this wouldn't
be much better than the list monad.

What really made this click for me was that the prompt type could be built
on a GADT:

] newtype GamePrompt a = GP (GameState, GameChoice a)
] data GameChoice a where
]-- pick a piece to act with
]ChoosePiece :: Player - GameChoice GamePiece
]-- pick how they should attack
]ChooseAttack :: Player - GamePiece - GameChoice AttackType
]-- etc.

Now you can use this type information as part of a handler function:
] gameIO :: GamePrompt a - IO a
] gameIO (GP (state, ChoosePiece player)) = getPiece state player
] gameIO (GP (state, ChooseAttack player piece)) = attackMenu player piece
] -- ...

The neat thing here is that the GADT specializes the type of IO a on the
right hand side.  So, getPiece state player has the type IO GamePiece,
not
the general IO a.  So the GADT is serving as a witness of the type of
response wanted by the game.

Another neat things is that, you don't need to embed this in the IO monad at
all; you could instead run a pure computation to do AI, or even use it for
unit testing!

 -- unit testing example
 data ScriptElem p where SE :: p a - a - ScriptElem p
 type Script p = [ScriptElem p]

 infix 1 --
 (--) = SE


] gameScript :: ScriptElem GameChoice - GameChoice a - Maybe a
] gameScript (SE (ChoosePiece _)piece)  (ChoosePiece _)= Just piece
] gameScript (SE (ChooseAttack _ _) attack) (ChooseAttack _ _) = Just attack
] gameScript _  _  = Nothing
]
] testGame :: Script GameChoice
] testGame =
]   [ ChoosePiece  P1-- Knight
]   , ChooseAttack P1 Knight -- Charge
]   , ChoosePiece  P2-- FootSoldier
]   , ...
]   ]

So, how to implement all of this?

 data Prompt (p :: * - *) :: (* - *) where
 PromptDone :: result - Prompt p result
 -- a is the type needed to continue the computation
 Prompt :: p a - (a - Prompt p result) - Prompt p result

This doesn't require GADT's; it's just using existential types, but I like
the aesthetics better this way.

Intuitively, a (Prompt p result) either gives you an immediate result
(PromptDone), or gives you a prompt which you need to reply to in order to
continue the computation.

This type is a MonadPrompt:

 instance Functor (Prompt p) where
fmap f (PromptDone r) = PromptDone (f r)
fmap f (Prompt p cont) = Prompt p (fmap f . cont)

 instance Monad (Prompt p) where
return = PromptDone
PromptDone r  = f = f r
Prompt p cont = f = Prompt p ((= f) . cont)

 instance MonadPrompt p (Prompt p) where
prompt p = Prompt p return

 -- Just for fun, make it work with StateT as well
 -- (needs -fallow-undecidable-instances)
 instance (Monad (t m), MonadTrans t, MonadPrompt p m) = MonadPrompt p (t
m) where
prompt = lift . prompt

The last bit to tie it together is an observation function which allows you
to
run the game:

 runPromptM :: Monad m = (forall a. p a - m a) - Prompt p r - m r
 runPromptM _ (PromptDone r) = return r
 runPromptM f (Prompt pa c)  = f pa = runPromptM f . c

 runPrompt :: (forall a. p a - a) - Prompt p r - r
 runPrompt f p = runIdentity $ runPromptM (Identity . f) p

 runScript :: 

[Haskell-cafe] Scheme in Haskell, Parsec Example, how to add scheme comments

2007-11-18 Thread Berlin Brown
I am sure many of you have looked at the scheme in haskell example that 
is on the web by Jonathan Tang. If you are familiar with the code, I 
need a little help trying to add scheme style comments:


; This is my comment

I added this code here and I think it works (I replaced the name 
parseSpaces with his spaces function).  But, if I start a line with a 
comment, it errors out with unbound variable.  Anybody have any ideas?


-- Added the ';'
symbol :: Parser Char
symbol = oneOf ;!$%|*+-/:=[EMAIL PROTECTED]

--
-- Handle whitespace and comments
parseSpaces :: Parser ()
parseSpaces = (try oneLineComment) | whiteSpace | return ()
   where
 whiteSpace = do skipMany1 space
 parseSpaces
 oneLineComment = do { try (string ;)
 ; skipMany (satisfy (/= '\n'))
 ; parseSpaces
 }

http://halogen.note.amherst.edu/~jdtang/scheme_in_48/tutorial/overview.html


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


[Haskell-cafe] Re: Scheme in Haskell, Parsec Example, how to add scheme comments

2007-11-18 Thread Berlin Brown
On Nov 18, 2007 7:32 PM, Berlin Brown [EMAIL PROTECTED] wrote:
 I am sure many of you have looked at the scheme in haskell example that
 is on the web by Jonathan Tang. If you are familiar with the code, I
 need a little help trying to add scheme style comments:

 ; This is my comment

 I added this code here and I think it works (I replaced the name
 parseSpaces with his spaces function).  But, if I start a line with a
 comment, it errors out with unbound variable.  Anybody have any ideas?

 -- Added the ';'
 symbol :: Parser Char
 symbol = oneOf ;!$%|*+-/:=[EMAIL PROTECTED]

 --
 -- Handle whitespace and comments
 parseSpaces :: Parser ()
 parseSpaces = (try oneLineComment) | whiteSpace | return ()
 where
   whiteSpace = do skipMany1 space
   parseSpaces
   oneLineComment = do { try (string ;)
   ; skipMany (satisfy (/= '\n'))
   ; parseSpaces
   }

 http://halogen.note.amherst.edu/~jdtang/scheme_in_48/tutorial/overview.html




Sorry, I am using the full scheme parser in this example:
http://halogen.note.amherst.edu/~jdtang/scheme_in_48/scheme_in_48.zip


-- 
Berlin Brown
http://botspiritcompany.com/botlist/spring/help/about.html
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Scheme in Haskell, Parsec Example, how to add scheme comments

2007-11-18 Thread Thomas Schilling
On Sun, 2007-11-18 at 19:37 -0500, Berlin Brown wrote:
 On Nov 18, 2007 7:32 PM, Berlin Brown [EMAIL PROTECTED] wrote:
  I am sure many of you have looked at the scheme in haskell example that
  is on the web by Jonathan Tang. If you are familiar with the code, I
  need a little help trying to add scheme style comments:
 
  ; This is my comment

The preferred way to do that is to use a token helper function:

  token :: P a - P a
  token p = do r - p
   whiteSpace
   return r

  -- or, if you add a Control.Applicative instance for your 
  -- parser type, this is just: token p = p * whiteSpace

Then you handle comments as whitespace:

  whiteSpace :: P ()
  whiteSpace = skipMany $
spaces 
| (char ';'  skipMany (satisfy (/='\n')))

Then you just use that like this:

  symbol :: P String
  symbol = token $ many1 $ satisfy $ not . (`elem` ()[]; )

See also Parsec's TokenParser.

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