Re[2]: [Haskell-cafe] Help with shootout

2006-01-03 Thread Bulat Ziganshin
Hello Chris,

Tuesday, January 03, 2006, 12:20:26 AM, you wrote:

CK   Einar Kartunen sped up the code using a custom channel implementation.
CKThis increased speed by a factor of over 2.  The wiki at
CK http://haskell.org/hawiki/ChameneosEntry has the latest version.

can these channels be used in general-purpose code?

CK   This makes me ponder one of the things that Joel was trying to do:
CK efficiently pass data to a logging thread.  It may be that a custom
CK channel would be helpful for that as well.

last variant of his code used just MVar-protected direct hPutStr
operations


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]



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


[Haskell-cafe] ST monad

2006-01-03 Thread Bulat Ziganshin
Hello

the following code can't go through typechecking. can anyone help me
to fix it or, better, let me know what i need to read to fix it myself? :)

import Control.Monad.ST
import Data.Array.ST
main = print $ runST $
   do arr - newArray (1,10) 127
  a - readArray arr 1
  writeArray arr 1 216
  b - readArray arr 1
  return (a,b)


PS: error message is

b.hs:4:15:
Inferred type is less polymorphic than expected
  Quantified type variable `s' escapes
  Expected type: ST s a - b
  Inferred type: (forall s1. ST s1 a) - a
In the first argument of `($)', namely `runST'
In the second argument of `($)', namely
`runST
 $ (do
  arr - newArray (1, 10) 127
  a - readArray arr 1
  writeArray arr 1 216
  b - readArray arr 1
  return (a, b))'

  

-- 
Best regards,
 Bulat  mailto:[EMAIL PROTECTED]



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


RE: [Haskell-cafe] ST monad

2006-01-03 Thread Ralf Lammel
... for the same reason as this one doesn't get through:

import Control.Monad.ST
import Data.Array.ST
main = print $ runST $
   do return ()

... but this one does:

import Control.Monad.ST
import Data.Array.ST
main = print $ runST (
   do return ())

it's all about rank-2 types; see SPJ's et al. paper on type inference
for these types. However, I guess that the jury is still out, say this
specific rank-2 behavior may be revised (and I also hope so).

HTH
Ralf


 -Original Message-
 From: [EMAIL PROTECTED] [mailto:haskell-cafe-
 [EMAIL PROTECTED] On Behalf Of Bulat Ziganshin
 Sent: Tuesday, January 03, 2006 2:28 AM
 To: haskell-cafe@haskell.org
 Subject: [Haskell-cafe] ST monad
 
 Hello
 
 the following code can't go through typechecking. can anyone help me
 to fix it or, better, let me know what i need to read to fix it
myself? :)
 
 import Control.Monad.ST
 import Data.Array.ST
 main = print $ runST $
do arr - newArray (1,10) 127
   a - readArray arr 1
   writeArray arr 1 216
   b - readArray arr 1
   return (a,b)
 
 
 PS: error message is
 
 b.hs:4:15:
 Inferred type is less polymorphic than expected
   Quantified type variable `s' escapes
   Expected type: ST s a - b
   Inferred type: (forall s1. ST s1 a) - a
 In the first argument of `($)', namely `runST'
 In the second argument of `($)', namely
 `runST
  $ (do
   arr - newArray (1, 10) 127
   a - readArray arr 1
   writeArray arr 1 216
   b - readArray arr 1
   return (a, b))'
 
 
 
 --
 Best regards,
  Bulat  mailto:[EMAIL PROTECTED]
 
 
 
 ___
 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] ST monad

2006-01-03 Thread oleg

Bulat Ziganshin wrote:

the following code can't go through typechecking
 import Control.Monad.ST
 import Data.Array.ST
 main = print $ runST $
do arr - newArray (1,10) 127
   a - readArray arr 1
   writeArray arr 1 216
   b - readArray arr 1
   return (a,b)


Indeed. The short answer: use 
runST (long expression) 
rather than
runST $ long expression 

when it comes to higher-ranked functions such as runST.
A longer answer:
http://www.haskell.org/pipermail/haskell-cafe/2004-December/008062.html

 let me know what i need to read to fix it myself
MLF (see Daan Leijen, A. Loeh, `Qualified types for MLF', ICFP05)


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


Re: [Haskell-cafe] Help with shootout

2006-01-03 Thread Chris Kuklewicz
Bulat Ziganshin wrote:
 Hello Chris,
 
 Tuesday, January 03, 2006, 12:20:26 AM, you wrote:
 
 CK   Einar Kartunen sped up the code using a custom channel implementation.
 CKThis increased speed by a factor of over 2.  The wiki at
 CK http://haskell.org/hawiki/ChameneosEntry has the latest version.
 
 can these channels be used in general-purpose code?

The latest Ch code is very very short:

 {- Ch : fast unordered channel implementation -}
 newtype Ch a = Ch (MVar [a], MVar a)
 
 newCh = liftM2 (,) (newMVar []) newEmptyMVar = return.Ch
 
 readCh (Ch (w,r)) = takeMVar w = \lst -
   case lst of (x:xs) - putMVar w xs  return x
   [] - putMVar w []  takeMVar r
 
 writeCh (Ch (w,r)) x = do
   ok - tryPutMVar r x -- opportunistic, helps for this problem
   unless ok $ takeMVar w = \lst - do 
 ok - tryPutMVar r x  -- safe inside take/put
 putMVar w $ if ok then lst else (x:lst)
 

It could be used in general purpose code, note the parametric type a
in Ch a.  It makes absolutely no guarantees about the order of values.
 That means that the order they are written is unlikely to be the order
in which they are read.  Writes to the channel are non-blocking and the
MVar [a] holds some items waiting to be read (in LIFO order).  The
MVar a allows a reader to block and wait for an empty channel to get
an item.  A small amount of extra speed comes from the writer's
opportunistic attempt to not take the w MVar unless it needs to.  But
note that readCh always takes the w MVar, and can ignore the r MVar.
This choice was determined by benchmarking.

Alternative, but slower for this case, functions for readCh and writeCh are

 readCh' (Ch (w,r)) = do
   mx - tryTakeMVar r
   case mx of
 Just x - return x
 Nothing - takeMVar w = \lst - case lst of (x:xs) - putMVar w xs  
 return x
   [] - putMVar w []  
 takeMVar r
 
 writeCh' (Ch (w,r)) x = takeMVar w = \lst - do 
 ok - tryPutMVar r x  -- safe inside take/put
 putMVar w $ if ok then lst else (x:lst)
 

But in this instance, using either of these would be slower.  The
balance between readers (one here) and writers (four here) and their
average speed is what determines the optimum readCh/writeCh code.
Different usage would benefit from different choices.

 
 CK   This makes me ponder one of the things that Joel was trying to do:
 CK efficiently pass data to a logging thread.  It may be that a custom
 CK channel would be helpful for that as well.
 
 last variant of his code used just MVar-protected direct hPutStr
 operations

My point was more that Haskell allows you to make your own channels and
that it is possible to do better than the provided ones.

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


[Haskell-cafe] file i/o

2006-01-03 Thread Robert Heffernan
Hi,

I am relatively new to Haskell and am finding i/o difficult to work
with.  I am trying to do something like the following:

I have a file of data, each line of which looks like this:
STRING,  INTEGER SEQUENCE
for example:
FOO ,2,1,4,3,6,7,5,9,10,11,8,13,12,

I would like to write a function the reads this file and returns
arrays like this:
[FOO,[2,1,4,3,6,7,5,9,10,11,8,13,12]]

Ideally, the function would return the first line when initially
called, the second the next time it is called and so on.  I would
settle for something that returned a big array comprising arrays of
the above type containing all the information in the file.  The file
is big, however.

I can not figure out how to do this from any of the tutorials so I
thought I might ask here.

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


Re: [Haskell-cafe] file i/o

2006-01-03 Thread Neil Mitchell
Hi Robert,

The first thing to mention is that Haskell uses linked-lists, not
arrays as the standard list type structure, so [1,2] is actually a
linked list.

The next thing to note is that Haskell is *lazy*. It won't do work
that it doens't have to. This means that you can return a linked list
with all the lines in the file, but they won't actually be read til
they are required. i.e. Haskell cleverly worries about all the
getting a next line as required stuff, without you even noticing -
it will read it line by line.

A simple function that does some of what you want is:
 parseFile :: FilePath - IO [(String, [Int])]
 parseFile x = do src - readFile x
  return (map parseLine (lines src))

 parseLine :: String - (String, [Int])
 parseLine = for you to write :)

The other point is that Haskell linked lists have to have every
element of the same type, so you can't have [test,1] as a linked
list, what you actually want is a tuple, written (test,1) - a tuple
is of fixed length and all elements can be of different type.

Hope that helps,

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


Re: [Haskell-cafe] Help with shootout

2006-01-03 Thread Joel Reymont
It seems like the real difference between TChan and the Ch code below  
is that TChan is, basically, [TVar a] whereas Ch is MVar [a], plus  
the order is guaranteed for a TChan.


Now why would it matter so much speed-wise?

This is the CVS code. newTChanIO is exported but undocumented in GHC  
6.4.1. I'm not sure what purpose it serves.


-- | 'TChan' is an abstract type representing an unbounded FIFO channel.
data TChan a = TChan (TVar (TVarList a)) (TVar (TVarList a))

type TVarList a = TVar (TList a)
data TList a = TNil | TCons a (TVarList a)

newTChan :: STM (TChan a)
newTChan = do
  hole - newTVar TNil
  read - newTVar hole
  write - newTVar hole
  return (TChan read write)

newTChanIO :: IO (TChan a)
newTChanIO = do
  hole - newTVarIO TNil
  read - newTVarIO hole
  write - newTVarIO hole
  return (TChan read write)

writeTChan :: TChan a - a - STM ()
writeTChan (TChan _read write) a = do
  listend - readTVar write -- listend == TVar pointing to TNil
  new_listend - newTVar TNil
  writeTVar listend (TCons a new_listend)
  writeTVar write new_listend

readTChan :: TChan a - STM a
readTChan (TChan read _write) = do
  listhead - readTVar read
  head - readTVar listhead
  case head of
TNil - retry
TCons a tail - do
writeTVar read tail
return a

On Jan 3, 2006, at 11:25 AM, Chris Kuklewicz wrote:


The latest Ch code is very very short:


{- Ch : fast unordered channel implementation -}
newtype Ch a = Ch (MVar [a], MVar a)

newCh = liftM2 (,) (newMVar []) newEmptyMVar = return.Ch

readCh (Ch (w,r)) = takeMVar w = \lst -
  case lst of (x:xs) - putMVar w xs  return x
  [] - putMVar w []  takeMVar r

writeCh (Ch (w,r)) x = do
  ok - tryPutMVar r x -- opportunistic, helps for this problem
  unless ok $ takeMVar w = \lst - do
ok - tryPutMVar r x  -- safe inside take/put
putMVar w $ if ok then lst else (x:lst)



It could be used in general purpose code, note the parametric type a
in Ch a.  It makes absolutely no guarantees about the order of  
values.
 That means that the order they are written is unlikely to be the  
order
in which they are read.  Writes to the channel are non-blocking and  
the

MVar [a] holds some items waiting to be read (in LIFO order).


--
http://wagerlabs.com/





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


Re: [Haskell-cafe] Help with shootout

2006-01-03 Thread Chris Kuklewicz
[ Deeply nested replies are starting to look similar to runListT $
runStateT $ runWriter  ]

[EMAIL PROTECTED] wrote:
 On Tue, Jan 03, 2006 at 12:07:43AM +, Joel Reymont wrote:
 
On Jan 2, 2006, at 9:20 PM, Chris Kuklewicz wrote:


 This makes me ponder one of the things that Joel was trying to do:
efficiently pass data to a logging thread.  It may be that a custom
channel would be helpful for that as well.

I have not taken the time to analyze the Chameneos code but need to  
point out that my problem was not with efficiently passing data to  
the logging thread. The issue was with data accumulating in the  
channel and the logger thread not reading it out fast enough.

The TChan implementation is a single-linked list implemented on top  
of TVar's. That would seem pretty efficient to me.
 
 
 It's simple and efficient but does nothing to prevent the channel from
 growing out of control.  A slightly modified (custom) channel based on
 TChan, but enforcing a maximum size (blocking on insert if the channel
 is too full), probably would have solved the problem.
 
 I assume that Erlang either does that or increases the priority of
 threads with large event queues, or both.
 
 Thanks,
 Matt Harden

Given that actually controlling priorities is not an option, adding
blocking like that makes sense.  One can make a ring buffer instead of a
singly linked list very easily.  In fact, I have that code lying around
(now attached).  It has not been speed optimized, but I did like being
able to express:

 type Node a = [TMVar a]

 make :: (Integral k) = k - STM (Node a)
 make k = liftM cycle $ sequence $ genericReplicate k newEmptyTMVar

It has the usual operations, but you need to pass a fixed size to
new/newEmpty and you also have an isFull test.  It has no operations to
resize the ring buffer created by make.
module ProdCons (PC,new,newEmpty, put,ProdCons.take,ProdCons.read,
   tryPut,tryTake,tryRead, isEmpty,isFull) where

{-  Fixed bounded-buffer size solution of producer/consumer problem.

Acts like a FIFO TMVar, blocking when capacity is reached.  So a
capacity of 1 behaves like a TMVar.

For arbitrary capacity just use a TChan. -}

import Control.Concurrent.STM
import Control.Concurrent
import Control.Monad.Fix
import Control.Monad
import Data.List(cycle,genericReplicate)

type Node a = [TMVar a]
newtype PC a = PC (TVar (Node a),TVar (Node a))

newEmpty :: (Integral k) = k - IO (PC a)
newEmpty k | k =0 = error Need capacity  0
   | otherwise = do 
  node - atomically $ make k
  atomically $ do
tv1 - newTVar node
tv2 - newTVar node
return (PC (tv1,tv2))

new :: (Integral k) = k - a - IO (PC a)
new k v | k =0 = error Need capacity  0
  v | otherwise = do 
  pc - newEmpty k 
  atomically $ put pc v 
  return pc

put ::PC a - a - STM ()
put (PC (tvar,_)) value = do 
  (tmvar:next) - readTVar tvar
  putTMVar tmvar value
  writeTVar tvar next

take :: PC a - STM a
take (PC (_,tvar)) = do
  (tmvar:next) - readTVar tvar
  value - takeTMVar tmvar
  writeTVar tvar next
  return value

read :: PC a - STM a
read (PC (_,tvar)) = do 
  (tmvar:_) - readTVar tvar
  readTMVar tmvar

tryTake :: PC a - STM (Maybe a)
tryTake pc = (ProdCons.take pc = return.Just) `orElse` (return Nothing)

tryRead :: PC a - STM (Maybe a)
tryRead pc = (ProdCons.read pc = return.Just) `orElse` (return Nothing)

tryPut :: PC a - a - STM Bool
tryPut pc v = (put pc v  return True) `orElse` (return False)

isEmpty :: PC a - STM Bool
isEmpty (PC (_,tvar)) = do
   (tmvar:_) - readTVar tvar
   isEmptyTMVar tmvar

isFull (PC (tvar,_)) = do
   (tmvar:_) - readTVar tvar
   empty - isEmptyTMVar tmvar
   return (not empty)

-- -- -- Internal -- -- --

make :: (Integral k) = k - STM (Node a)
make k = liftM cycle $ sequence $ genericReplicate k newEmptyTMVar
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] file i/o

2006-01-03 Thread Thomas Davie
The other thing to mention, is that if you have the ability to change  
file formats, it may be better to make just a slight adjustment... If  
you make it look exactly like the haskell data structure you want:


[(Foo, [1,2,3,4,5,6,7])
,(Bar, [7,6,5,4,3,2,1])
,...]

Then your parser becomes even simpler:

parseFile :: FilePath - IO [(String,[Int])]
parseFile = do src - readFile x
   return $ read src

On Jan 3, 2006, at 11:33 AM, Neil Mitchell wrote:


Hi Robert,

The first thing to mention is that Haskell uses linked-lists, not
arrays as the standard list type structure, so [1,2] is actually a
linked list.

The next thing to note is that Haskell is *lazy*. It won't do work
that it doens't have to. This means that you can return a linked list
with all the lines in the file, but they won't actually be read til
they are required. i.e. Haskell cleverly worries about all the
getting a next line as required stuff, without you even noticing -
it will read it line by line.

A simple function that does some of what you want is:

parseFile :: FilePath - IO [(String, [Int])]
parseFile x = do src - readFile x
 return (map parseLine (lines src))



parseLine :: String - (String, [Int])
parseLine = for you to write :)


The other point is that Haskell linked lists have to have every
element of the same type, so you can't have [test,1] as a linked
list, what you actually want is a tuple, written (test,1) - a tuple
is of fixed length and all elements can be of different type.

Hope that helps,

Neil
___
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] Haskell vs. Erlang: Logging to one thread from thousands /Answer/

2006-01-03 Thread Joel Reymont

I asked the Erlang guys why I can log to a single process in Erlang
without any problems. The scheduler could well be round-robin
but since the message queue is hard-wired to each Erlang process
they found an elegant way out.

--
There is a small fix in the scheduler for the standard
producer/consumer problem: A process that sends to a
receiver having a large receive queue gets punished
with a large reduction (number of function calls)
count for the send operation, and will therefore
get smaller scheduling slots.
--

Thanks, Joel

--
http://wagerlabs.com/





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


[Haskell-cafe] Re: Joels Time Leak

2006-01-03 Thread Simon Marlow

Tomasz Zielonka wrote:

On Thu, Dec 29, 2005 at 01:20:41PM +, Joel Reymont wrote:

Why does it take a fraction of a second for 1 thread to unpickle and  
several seconds per thread for several threads to do it at the same  
time? I think this is where the mistery lies.



Have you considered any of this:

- too big memory pressure: more memory means more frequent and more
  expensive GCs, 1000 threads using so much memory means bad cache
  performance
- a deficiency of GHC's thread scheduler - giving too much time one
  thread steals it from others (Simons, don't get angry at me - I am
  probably wrong here ;-)


I don't think there's anything really strange going on here.

The default context switch interval in GHC is 0.02 seconds, measured in 
CPU time by default.  GHC's scheduler is stricly round-robin, so 
therefore with 100 threads in the system it can be 2 seconds between a 
thread being descheduled and scheduled again.


I measured the time taken to unpickle those large 50k packets as 0.3 
seconds on my amd64 box (program compiled *without* optimisation), so 
the thread can get descheduled twice during while unpickling a large 
packet, giving a 4s delay with 100 threads running.


The actual context switch interval seems to often be larger than 0.2 
seconds; I'm not sure exactly why this is, it might be due to delays in 
the OS delivering the signal.  This does mean that the timeleak program 
reports alerts for as little as 50 threads, though.


Cheers,
Simon

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


[Haskell-cafe] Haskell vs. Erlang: The scheduler

2006-01-03 Thread Joel Reymont

On Jan 3, 2006, at 2:30 PM, Simon Marlow wrote:
The default context switch interval in GHC is 0.02 seconds,  
measured in CPU time by default.  GHC's scheduler is stricly round- 
robin, so therefore with 100 threads in the system it can be 2  
seconds between a thread being descheduled and scheduled again.


I measured the time taken to unpickle those large 50k packets as  
0.3 seconds on my amd64 box (program compiled *without*  
optimisation), so the thread can get descheduled twice during while  
unpickling a large packet, giving a 4s delay with 100 threads  
running.


Is it impractical then to implement this type of app in Haskell?  
Based on the nature of Haskell scheduling I would be inclined to say  
yes. I'm including information on the Erlang scheduler below.


I think it's possible to emulate the workings of the Erlang scheduler  
in Haskell by using delimited continuations a-la Zipper File Server/ 
OS. A single delimited continuation (request in Zipper FS parlance?)  
would be a scheduling unit and a programmer could then tune the  
scheduler to their hearts content.


Apart from putting a lot of burden on the programmer this becomes  
quite troublesome when multiple sockets or file descriptors are  
concerned. There's no easy way to plug into the select facility of  
the Haskell runtime to receive notifications of input available. You  
will notice the Zipper FS spending quite a few lines of code to roll  
its own select facility.


The Erlang scheduler is based on reduction count where one reduction  
is roughly equivalent to a function call. See http://www.erlang.org/ 
ml-archive/erlang-questions/200104/msg00072.html for more detail.


There's also this helpful bit of information:

--
erlang:bump_reductions(Reductions) - void()

Types  Reductions = int()

This implementation-dependent function increments the  reduction
counter  for  the  calling  process.  In  the Beam emulator, the
reduction counter is normally incremented by one for each  func-
tion  and  BIF  call,  and  a  context switch is forced when the
counter reaches 1000.
--

Regarding the issue of why a logger process in Erlang does not get  
overwhelved, this is the reply I got from Raimo Niskanen (Erlang team  
at Ericsson):


There is a small fix in the scheduler for the standard
producer/consumer problem: A process that sends to a
receiver having a large receive queue gets punished
with a large reduction (number of function calls)
count for the send operation, and will therefore
get smaller scheduling slots.

Thanks, Joel

--
http://wagerlabs.com/





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


Re: [Haskell-cafe] Re: Joels Time Leak

2006-01-03 Thread Sebastian Sylvan
On 1/3/06, Simon Marlow [EMAIL PROTECTED] wrote:
 Tomasz Zielonka wrote:
  On Thu, Dec 29, 2005 at 01:20:41PM +, Joel Reymont wrote:
 
 Why does it take a fraction of a second for 1 thread to unpickle and
 several seconds per thread for several threads to do it at the same
 time? I think this is where the mistery lies.
 
 
  Have you considered any of this:
 
  - too big memory pressure: more memory means more frequent and more
expensive GCs, 1000 threads using so much memory means bad cache
performance
  - a deficiency of GHC's thread scheduler - giving too much time one
thread steals it from others (Simons, don't get angry at me - I am
probably wrong here ;-)

 I don't think there's anything really strange going on here.

 The default context switch interval in GHC is 0.02 seconds, measured in
 CPU time by default.  GHC's scheduler is stricly round-robin, so
 therefore with 100 threads in the system it can be 2 seconds between a
 thread being descheduled and scheduled again.

According to this:
http://www.haskell.org/ghc/docs/latest/html/users_guide/sec-using-parallel.html#parallel-rts-opts

The minimum time between context switches is 20 milliseconds.

Is there any good reason why 0.02 seconds is the best that you can get
here? Couldn't GHC's internal timer tick at a _much_ faster rate (like
50-100µs or so)?
Apart from meaning big trouble for applications with a large number of
threads (such as Joels) it'll also make life difficult for any sort of
real-time application. For instance if you want to use HOpenGL to
render a simulation engine and you split it up into tons of concurrent
processes (say one for each dynamic entity in the engine), the 20ms
granularity would make it quite hard to achieve 60 frames per second
in that case...

/S

--
Sebastian Sylvan
+46(0)736-818655
UIN: 44640862
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Joels Time Leak

2006-01-03 Thread Chris Kuklewicz
General follow-up questions:

Would adding Control.Concurrent.yield commands cause a context switch
more often than every 0.02 seconds?

Is there any command in GHC to allow a thread to prevent itself from
being rescheduled while computing something?

Another comment: between 1000's of threads and writing a custom
continuation based scheduler, what about using a thread pool?  Does
anyone have a library with a fork-IO-Pool command?

-- 
Chris

Simon Marlow wrote:
 Tomasz Zielonka wrote:
 
 On Thu, Dec 29, 2005 at 01:20:41PM +, Joel Reymont wrote:

 Why does it take a fraction of a second for 1 thread to unpickle and 
 several seconds per thread for several threads to do it at the same 
 time? I think this is where the mistery lies.



 Have you considered any of this:

 - too big memory pressure: more memory means more frequent and more
   expensive GCs, 1000 threads using so much memory means bad cache
   performance
 - a deficiency of GHC's thread scheduler - giving too much time one
   thread steals it from others (Simons, don't get angry at me - I am
   probably wrong here ;-)
 
 
 I don't think there's anything really strange going on here.
 
 The default context switch interval in GHC is 0.02 seconds, measured in
 CPU time by default.  GHC's scheduler is stricly round-robin, so
 therefore with 100 threads in the system it can be 2 seconds between a
 thread being descheduled and scheduled again.
 
 I measured the time taken to unpickle those large 50k packets as 0.3
 seconds on my amd64 box (program compiled *without* optimisation), so
 the thread can get descheduled twice during while unpickling a large
 packet, giving a 4s delay with 100 threads running.
 
 The actual context switch interval seems to often be larger than 0.2
 seconds; I'm not sure exactly why this is, it might be due to delays in
 the OS delivering the signal.  This does mean that the timeleak program
 reports alerts for as little as 50 threads, though.
 
 Cheers,
 Simon
 
 ___
 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: Haskell vs. Erlang: The scheduler

2006-01-03 Thread Simon Marlow
On 03 January 2006 15:13, Joel Reymont wrote:

 On Jan 3, 2006, at 2:30 PM, Simon Marlow wrote:
 The default context switch interval in GHC is 0.02 seconds,
 measured in CPU time by default.  GHC's scheduler is stricly round-
 robin, so therefore with 100 threads in the system it can be 2
 seconds between a thread being descheduled and scheduled again.
 
 I measured the time taken to unpickle those large 50k packets as
 0.3 seconds on my amd64 box (program compiled *without*
 optimisation), so the thread can get descheduled twice during while
 unpickling a large packet, giving a 4s delay with 100 threads
 running.
 
 Is it impractical then to implement this type of app in Haskell?
 Based on the nature of Haskell scheduling I would be inclined to say
 yes.

Absolutely not!

Apart from the problem you have with a space leak caused by the input
buffer of the logging thread overflowing, which is easily fixed by using
a bounded channel, I don't know why you want priorities.  Is there
something else?

We could easily add Erlang-style priorities (though without the overhead
of counting function calls, I'd do it by counting allocations), but I'd
rather not if we can avoid it.

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


RE: [Haskell-cafe] Re: Joels Time Leak

2006-01-03 Thread Simon Marlow
On 03 January 2006 15:37, Sebastian Sylvan wrote:

 On 1/3/06, Simon Marlow [EMAIL PROTECTED] wrote:
 Tomasz Zielonka wrote:
 On Thu, Dec 29, 2005 at 01:20:41PM +, Joel Reymont wrote:
 
 Why does it take a fraction of a second for 1 thread to unpickle
 and several seconds per thread for several threads to do it at the
 same time? I think this is where the mistery lies.
 
 
 Have you considered any of this:
 
 - too big memory pressure: more memory means more frequent and more
   expensive GCs, 1000 threads using so much memory means bad cache 
 performance - a deficiency of GHC's thread scheduler - giving too
   much time one thread steals it from others (Simons, don't get
   angry at me - I am probably wrong here ;-)
 
 I don't think there's anything really strange going on here.
 
 The default context switch interval in GHC is 0.02 seconds, measured
 in CPU time by default.  GHC's scheduler is stricly round-robin, so
 therefore with 100 threads in the system it can be 2 seconds between
 a thread being descheduled and scheduled again.
 
 According to this:
 http://www.haskell.org/ghc/docs/latest/html/users_guide/sec-using-parallel.html#parallel-rts-opts
 
 The minimum time between context switches is 20 milliseconds.
 
 Is there any good reason why 0.02 seconds is the best that you can get
 here? Couldn't GHC's internal timer tick at a _much_ faster rate (like
 50-100µs or so)?

Sure, there's no reason why we couldn't do this.  Of course, even idle Haskell 
processes will be ticking away in the background, so there's a reason not to 
make the interval too short.  What do you think is reasonable?

 Apart from meaning big trouble for applications with a large number of
 threads (such as Joels) it'll also make life difficult for any sort of
 real-time application. For instance if you want to use HOpenGL to
 render a simulation engine and you split it up into tons of concurrent
 processes (say one for each dynamic entity in the engine), the 20ms
 granularity would make it quite hard to achieve 60 frames per second
 in that case...

The reason things are the way they are is that a large number of *running* 
threads is not a workload we've optimised for.  In fact, Joel's program is the 
first one I've seen with a lot of running threads, apart from our testsuite.  
And I suspect that when Joel uses a better binary I/O implementation a lot of 
that CPU usage will disappear.

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


Re: [Haskell-cafe] Re: Joels Time Leak

2006-01-03 Thread Sebastian Sylvan
On 1/3/06, Simon Marlow [EMAIL PROTECTED] wrote:
 On 03 January 2006 15:37, Sebastian Sylvan wrote:

  On 1/3/06, Simon Marlow [EMAIL PROTECTED] wrote:
  Tomasz Zielonka wrote:
  On Thu, Dec 29, 2005 at 01:20:41PM +, Joel Reymont wrote:
 
  Why does it take a fraction of a second for 1 thread to unpickle
  and several seconds per thread for several threads to do it at the
  same time? I think this is where the mistery lies.
 
 
  Have you considered any of this:
 
  - too big memory pressure: more memory means more frequent and more
expensive GCs, 1000 threads using so much memory means bad cache
  performance - a deficiency of GHC's thread scheduler - giving too
much time one thread steals it from others (Simons, don't get
angry at me - I am probably wrong here ;-)
 
  I don't think there's anything really strange going on here.
 
  The default context switch interval in GHC is 0.02 seconds, measured
  in CPU time by default.  GHC's scheduler is stricly round-robin, so
  therefore with 100 threads in the system it can be 2 seconds between
  a thread being descheduled and scheduled again.
 
  According to this:
  http://www.haskell.org/ghc/docs/latest/html/users_guide/sec-using-parallel.html#parallel-rts-opts
 
  The minimum time between context switches is 20 milliseconds.
 
  Is there any good reason why 0.02 seconds is the best that you can get
  here? Couldn't GHC's internal timer tick at a _much_ faster rate (like
  50-100µs or so)?

 Sure, there's no reason why we couldn't do this.  Of course, even idle 
 Haskell processes will be ticking away in the background, so there's a reason 
 not to make the interval too short.  What do you think is reasonable?

Not sure. Could it be configurable via a command line flag? If the
profiler could report the % of time spent doing context switches (or
maybe it already does?) the user could fine tune this to his liking.

For the (hypothetical) real-time simulation app I would *guess* that
something along the lines of 500µs would be more than enough to not
introduce any unnecessary lag in rendering (seeing as the target frame
time would be around 15ms, and you'd want to have a good amount of
context switches to allow some of the next frame to be computed in
parallell to all the render-surface optimizations etc. for the current
frame).

But then again, there may be other apps which need it to be even
lower.. So a command line flag sure would be nice.

/S

--
Sebastian Sylvan
+46(0)736-818655
UIN: 44640862
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Joels Time Leak

2006-01-03 Thread Joel Reymont

Simon,

I don't think CPU usage is the issue. An individual thread will take  
a fraction of a second to deserialize a large packet. The issue is  
that, as you pointed out, you can get alerts even with 50 threads.  
Those fractions of a second add up in a certain way that's  
detrimental to the performance of the app.


The timeleak code uses Ptr Word8 to pickle which should be very  
efficient. I believe the delay comes from the way 'sequ' is compiled  
by GHC. I'll take the liberty of quoting Andrew Kennedy (your  
colleague from MS Research) who wrote the picklers:


--
My original pickler implementation was for SML. It was used in the  
MLj compiler, and is still used in the SML.NET compiler, and has  
acceptable performance (few ms pickling/unpickling for typical  
intermediate language object files). I must admit that I've not used  
the Haskell variant in anger. Apart from the inherent slowdown  
associated with laziness, is there a particular reason for poor  
performance?

--

'sequ' by itself does not seem like a big deal but when used to model  
records it builds a large nested lambda-list and I don't think that  
list is being compiled efficiently. I would appreciate if you could  
look at that and issue a verdict now that Andrew cofirms using the  
picklers in a real-life environment and w/o major problems.


Suppose I chose a different implementation of binary IO and disposed  
of pickler combinators.  Suppose I gained a 2x speed-up by doing so.  
I would now be getting alerts with 100 threads instead of 50, no?  
That's still far from ideal.


Joel

On Jan 3, 2006, at 4:43 PM, Simon Marlow wrote:

The reason things are the way they are is that a large number of  
*running* threads is not a workload we've optimised for.  In fact,  
Joel's program is the first one I've seen with a lot of running  
threads, apart from our testsuite.  And I suspect that when Joel  
uses a better binary I/O implementation a lot of that CPU usage  
will disappear.


--
http://wagerlabs.com/





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


[Haskell-cafe] How to print a string (lazily)

2006-01-03 Thread Daniel Carrera

Hello,

I've been studying more Haskell and I've improved a lot. But I just hit 
a small problem. I want to print all the elements of a linst (putStr). 
I'd like to write something like this:


print_list [] = do putStr 
print_list (x:xs) = (do putStr x)  print_list xs

I know this is wrong, but I hope you can see what I'm trying to do.

I know of other ways I could print a list. For example:

print_list xs = do putStr(join xs)
where join [] = 
  join (x:xs) = (show x) ++ \n ++ join xs

But the thing is, I want to write a lazy version of this function. It's 
not that I need such a function, I'm just trying to learn Haskell.


Any suggestions?

Question: What do you call a function that has side-effects? (like 
putStr) I know that function is the wrong term.


Cheers,
Daniel.
--
 /\/`) http://oooauthors.org
/\/_/  http://opendocumentfellowship.org
   /\/_/
   \/_/I am not over-weight, I am under-tall.
   /
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Joels Time Leak

2006-01-03 Thread Chris Kuklewicz
Thanks for the answer, but I should I written a longer comment. I have
added such a longer comment below:

Simon Marlow wrote:
 Chris Kuklewicz wrote:
 
 Another comment: between 1000's of threads and writing a custom
 continuation based scheduler, what about using a thread pool?  Does
 anyone have a library with a fork-IO-Pool command?
 
 
 You don't need a thread pool, because threads are so cheap.  Thread
 pools are just a workaround for lack of lightweight concurrency.
 
 Cheers,
 Simon
 

Since the round-robin scheduler has (0.02 * N) seconds of delay for N
therads, then one could trade off latency between time spent waiting for
the thread pool to start a job and time spend running the job and
getting interrupted.

In the limit of 1 worker thread, all the latency is waiting to get run,
and there are no interruptions, so the time taken *while running* is
very short.  With 10 threads, there can be a delay to start, and each
interruption adds 0.2 seconds to the job's run time once it has started.

For a server, the client requests queue up and wait for room in the
thread pool, and the pool is kept small enough that the
round-robin-schedular-delay keeps requests from timing out while being
serviced.  Otherwise 1000 client requests would cause 20 seconds of
reschedule penalty for all threads and they could all timeout.  With a
thread pool, one can drop threads that have been waiting for too long
instead of running them, so those threads will timeout. But the pool
keeps servicing at least some of the client requests on time.

All hypothetical to me, of course.

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


Re: [Haskell-cafe] How to print a string (lazily)

2006-01-03 Thread Christian Maeder

Daniel Carrera wrote:

print_list xs = do putStr(join xs)
where join [] = 
  join (x:xs) = (show x) ++ \n ++ join xs


print_list xs = mapM putStrLn xs

Question: What do you call a function that has side-effects? (like 
putStr) I know that function is the wrong term.


action, command, program, etc.

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


Re: [Haskell-cafe] How to print a string (lazily)

2006-01-03 Thread Chris Kuklewicz
Daniel Carrera wrote:
 Hello,
 
 I've been studying more Haskell and I've improved a lot. But I just hit
 a small problem. I want to print all the elements of a linst (putStr).
 I'd like to write something like this:
 
 print_list [] = do putStr 
 print_list (x:xs) = (do putStr x)  print_list xs
 
 I know this is wrong, but I hope you can see what I'm trying to do.
 
 I know of other ways I could print a list. For example:
 
 print_list xs = do putStr(join xs)
 where join [] = 
   join (x:xs) = (show x) ++ \n ++ join xs
 
 But the thing is, I want to write a lazy version of this function. It's
 not that I need such a function, I'm just trying to learn Haskell.
 
 Any suggestions?
 
 Question: What do you call a function that has side-effects? (like
 putStr) I know that function is the wrong term.
 
 Cheers,
 Daniel.

I sometimes call a function with side-effects in IO a command.  But
the terms are fungible.  But calling putStr a function is correct.  It
is not a pure function however.

What does lazy printing mean?

I assume it means you evaluate the head of the list, print it, then
recursively do this for the tail of the list.  With an infinite list you
will get inifinite output.

I assume it does not mean you evaluate the whole list before printing
anything.  This would prevent infinite lists from producing output.

(mapM_ putStr) or (mapM_ putStrLn) will do what you want.

All of these commands show work, even if hw is inifitely long:

let printList [] = return ()
printList (x:xs) = do putStrLn x
  printList xs

main = do
  let hw = [Hello, ,World,!]
  mapM_ putStr hw
  mapM_ putStrLn hw
  putStr (unlines hw) -- see also: unwords, words, lines
  printList hw

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


Re: [Haskell-cafe] How to print a string (lazily)

2006-01-03 Thread Neil Mitchell
Hi,

All Haskell functions are lazy, hence there is no need to write a
lazy version of your print_list function. I think the function you
probably want is:

putStr (unlines xs)

This uses the bulid in unlines function, which is similar in spirit to
join (you get more quotes, which I guess you don't want)

The equivalent in monad'y programming is:

mapM putStrLn xs

The first one has fewer monads, so I prefer it, but take your pick :)

Thanks

Neil


On 1/3/06, Daniel Carrera [EMAIL PROTECTED] wrote:
 Hello,

 I've been studying more Haskell and I've improved a lot. But I just hit
 a small problem. I want to print all the elements of a linst (putStr).
 I'd like to write something like this:

 print_list [] = do putStr 
 print_list (x:xs) = (do putStr x)  print_list xs

 I know this is wrong, but I hope you can see what I'm trying to do.

 I know of other ways I could print a list. For example:

 print_list xs = do putStr(join xs)
 where join [] = 
   join (x:xs) = (show x) ++ \n ++ join xs

 But the thing is, I want to write a lazy version of this function. It's
 not that I need such a function, I'm just trying to learn Haskell.

 Any suggestions?

 Question: What do you call a function that has side-effects? (like
 putStr) I know that function is the wrong term.

 Cheers,
 Daniel.
 --
   /\/`) http://oooauthors.org
  /\/_/  http://opendocumentfellowship.org
 /\/_/
 \/_/I am not over-weight, I am under-tall.
 /
 ___
 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] How to print a string (lazily)

2006-01-03 Thread Adrian Hey
On Tuesday 03 Jan 2006 5:37 pm, Christian Maeder wrote:
 Daniel Carrera wrote:

  Question: What do you call a function that has side-effects? (like
  putStr) I know that function is the wrong term.

 action, command, program, etc.

Actually (at the risk of appearing pedantic), I think it's important
to make clear that function *is* the correct term for putStr..
 putStr :: String - IO ()
It's expressions like (putStr Hello World) of type IO something
that are (what I would call) actions.

Haskell has no name for functions that have side-effects.
They don't exist (well not unless you're grossly abusing
unsafePerformIO).

Regards
--
Adrian Hey



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


Re: [Haskell-cafe] How to print a string (lazily)

2006-01-03 Thread Sebastian Sylvan
On 1/3/06, Daniel Carrera [EMAIL PROTECTED] wrote:
 Hello,

 I've been studying more Haskell and I've improved a lot. But I just hit
 a small problem. I want to print all the elements of a linst (putStr).
 I'd like to write something like this:

 print_list [] = do putStr 
 print_list (x:xs) = (do putStr x)  print_list xs


Others have already replied with a solution, but it looks to me like
what you're missing is how to sequence commands, which is the whole
purpose of the do notation.

print_list [] = return ()
print_list (x:xs) =
  do putStr x
   print_list xs

The do notation is used here to sequence to IO actions (which answers
your second question), first it prints out the first character in the
string, then it calls itself recursively to print the rest of the
list.
The empty list shouldn't print an empty string, it should do nothing
(that is, just return IO () because that's the return type of
print_list)

/S
--
Sebastian Sylvan
+46(0)736-818655
UIN: 44640862
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] How to print a string (lazily)

2006-01-03 Thread Daniel Carrera

Sebastian Sylvan wrote:

Others have already replied with a solution, but it looks to me like
what you're missing is how to sequence commands, which is the whole
purpose of the do notation.

print_list [] = return ()
print_list (x:xs) =
  do putStr x
   print_list xs

The do notation is used here to sequence to IO actions (which answers
your second question), first it prints out the first character in the
string, then it calls itself recursively to print the rest of the
list.


Thanks! And yes, I'm just learning how to sequence commands/actions, so 
I know I'm missing a lot.



The empty list shouldn't print an empty string, it should do nothing
(that is, just return IO () because that's the return type of
print_list)


Yeah... I just didn't know how to do nothing with Haskell. Thanks!

Cheers,
Daniel.
--
 /\/`) http://oooauthors.org
/\/_/  http://opendocumentfellowship.org
   /\/_/
   \/_/I am not over-weight, I am under-tall.
   /
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] How to print a string (lazily)

2006-01-03 Thread Daniel Carrera

Chris Kuklewicz wrote:

What does lazy printing mean?

I assume it means you evaluate the head of the list, print it, then
recursively do this for the tail of the list.  With an infinite list you
will get inifinite output.

I assume it does not mean you evaluate the whole list before printing
anything.  This would prevent infinite lists from producing output.


Yes, that's exactly what I had in mind. I wanted to print [1..] (an 
infinite list) with each number on a different line.


Thanks for the help. Yes, the function works now.


main = do
  let hw = [Hello, ,World,!]
  mapM_ putStr hw
  mapM_ putStrLn hw
  putStr (unlines hw) -- see also: unwords, words, lines
  printList hw


Cool. I didn't know about (un)words and unlines.

Cheers,
Daniel.
--
 /\/`) http://oooauthors.org
/\/_/  http://opendocumentfellowship.org
   /\/_/
   \/_/I am not over-weight, I am under-tall.
   /
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] How to print a string (lazily)

2006-01-03 Thread Donn Cave
On Tue, 3 Jan 2006, Chris Kuklewicz wrote:
...
 I sometimes call a function with side-effects in IO a command.  But
 the terms are fungible.  But calling putStr a function is correct.  It
 is not a pure function however.

Is that the standard party line?  I mean, we all know its type and
semantics, whatever you want to call them, but if we want to put names
to things, I had the impression that the IO monad is designed to work
in a pure functional language - so that the functions are indeed actually
pure, including putStr.  It's the monad that actually incurs the side
effects.  Or something like that.  So it isn't at all necessary to have
another word for functions of type IO a.

Donn Cave, [EMAIL PROTECTED]

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


Re: [Haskell-cafe] How to print a string (lazily)

2006-01-03 Thread Daniel Carrera

Neil Mitchell wrote:

All Haskell functions are lazy, hence there is no need to write a
lazy version of your print_list function. I think the function you
probably want is:

putStr (unlines xs)


Hhmm... that does work, and I'm a bit surprised that it does. I guess 
I'm still stuck in the eager computation mindset. I would expect putStr 
to have to wait for the (unlines xs) to be finished before doing any 
printing, but it doesn't.


Some day I'll get the hang of this lazy evaluation thing. :)


The first one has fewer monads, so I prefer it, but take your pick :)


Monads scare me, so I'll pick the first :)  Thanks!

Cheers,
Daniel.
--
 /\/`) http://oooauthors.org
/\/_/  http://opendocumentfellowship.org
   /\/_/
   \/_/I am not over-weight, I am under-tall.
   /
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] How to print a string (lazily)

2006-01-03 Thread Sebastian Sylvan
On 1/3/06, Daniel Carrera [EMAIL PROTECTED] wrote:
 Neil Mitchell wrote:
  All Haskell functions are lazy, hence there is no need to write a
  lazy version of your print_list function. I think the function you
  probably want is:
 
  putStr (unlines xs)

 Hhmm... that does work, and I'm a bit surprised that it does. I guess
 I'm still stuck in the eager computation mindset. I would expect putStr
 to have to wait for the (unlines xs) to be finished before doing any
 printing, but it doesn't.

 Some day I'll get the hang of this lazy evaluation thing. :)

It does, in a sense, but since unlines is lazy (just like *everything
else* in Haskell) it won't actually *do* anything until putStr demands
an element from the result.

/S

--
Sebastian Sylvan
+46(0)736-818655
UIN: 44640862
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] How to print a string (lazily)

2006-01-03 Thread Adrian Hey
On Tuesday 03 Jan 2006 6:11 pm, Donn Cave wrote:
 On Tue, 3 Jan 2006, Chris Kuklewicz wrote:
 ...

  I sometimes call a function with side-effects in IO a command.  But
  the terms are fungible.  But calling putStr a function is correct.  It
  is not a pure function however.

 Is that the standard party line?

I don't think so. putStr certainly is a pure function.
Try running..
main :: IO ()
main = let action = putStr Bye
   in action `seq` action
..and see what happens.

Regards
--
Adrian Hey




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


Re: [Haskell-cafe] How to print a string (lazily)

2006-01-03 Thread Ezra Cooper

On Jan 3, 2006, at 6:30 PM, Sebastian Sylvan wrote:


On 1/3/06, Daniel Carrera [EMAIL PROTECTED] wrote:

Neil Mitchell wrote:

All Haskell functions are lazy, hence there is no need to write a
lazy version of your print_list function. I think the function you
probably want is:

putStr (unlines xs)


Hhmm... that does work, and I'm a bit surprised that it does. I guess
I'm still stuck in the eager computation mindset. I would expect 
putStr

to have to wait for the (unlines xs) to be finished before doing any
printing, but it doesn't.

Some day I'll get the hang of this lazy evaluation thing. :)


It does, in a sense, but since unlines is lazy (just like *everything
else* in Haskell) it won't actually *do* anything until putStr demands
an element from the result.


... and, significantly, putStr will demand those elements one at a 
time; each element of the list is, in turn, evaluated lazily, producing 
(a) a next element and (b) a thunk representing the rest of the list.


In your example 'join' function,

  join [] = 
  join (x:xs) = (show x) ++ \n ++ join xs

the caller will demand the first element of the list, which will force 
the evaluation of (show x) but it will not immediately force the 
evaluation of (join xs). That part stays as it is, living life as a 
thunk, until the caller has demanded all the preceding elements and 
still wants more.


hth,
Ezra

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


Re: [Haskell-cafe] How to print a string (lazily)

2006-01-03 Thread Cale Gibbard
On 03/01/06, Donn Cave [EMAIL PROTECTED] wrote:
 On Tue, 3 Jan 2006, Chris Kuklewicz wrote:
 ...
  I sometimes call a function with side-effects in IO a command.  But
  the terms are fungible.  But calling putStr a function is correct.  It
  is not a pure function however.

 Is that the standard party line?  I mean, we all know its type and
 semantics, whatever you want to call them, but if we want to put names
 to things, I had the impression that the IO monad is designed to work
 in a pure functional language - so that the functions are indeed actually
 pure, including putStr.  It's the monad that actually incurs the side
 effects.  Or something like that.  So it isn't at all necessary to have
 another word for functions of type IO a.

I'd say it depends on the way that you're thinking about it. Strictly
speaking, putStr is a pure function which returns an action. It's also
referentially transparent, since it always returns the same action for
the same string.

However, if you think of functions a - IO b as the arrows a - b in a
new category where composition is Kleisli composition:

(@@) :: Monad m = (a - m b) - (t - m a) - (t - m b)
y @@ x = \u - x u = y

Then these arrows are effectful and would be considered impure.

I think I prefer the first explanation, as it's a somewhat important
property that the same action is computed for the same input. This
doesn't hold of side-effectful arrows in general. Note that with
Hughes' Arrows, this restriction can (often quite cleverly) be
side-stepped in order to make some rather major optimisations.

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


Re: [Haskell-cafe] Catching string from error function with GHC Control.Exception

2006-01-03 Thread Iain Alexander
I've just been through the process of converting some code from using 
Control.Exception to 
using an Error monad, and I would recommend that as a more straightforward and 
manageable alternative, unless you need Control.Exception for other reasons.

I started by changing my potentially-failing functions to return Either 
Exception a,
where Exception is my own user-defined error type, but you could use String, 
and a is the 
type of the real return value.  I initially used explicit Left and Right to 
construct appropriate 
values.  My testing code is hand-written, and explicitly matched against Left e 
and Right x to 
decode the return value.

I ended up with functions returning MonadError Exception m = m a, using 
throwError and 
return to construct appropriate values.  My testing code uses
ErrorT Exception (StateT s IO) a
to manage a combination of error-handling, state (an error count) and IO, with 
the option of 
using Either Exception to test expected errors for individual cases.
-- 
Iain Alexander  [EMAIL PROTECTED]


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


Re: [Haskell-cafe] Re: Joels Time Leak

2006-01-03 Thread Tomasz Zielonka
On Tue, Jan 03, 2006 at 02:30:53PM +, Simon Marlow wrote:
 I measured the time taken to unpickle those large 50k packets as 0.3 
 seconds on my amd64 box (program compiled *without* optimisation), so 
 the thread can get descheduled twice during while unpickling a large 
 packet, giving a 4s delay with 100 threads running.

I might have made an error when counting the packets. I simply placed a
putStrLn in read, but some of the packets are nested
(SrvCompressedCommands), so read is called more than once for a
top-level packet.

Best regards
Tomasz

-- 
I am searching for programmers who are good at least in
(Haskell || ML)  (Linux || FreeBSD || math)
for work in Warsaw, Poland
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Joels Time Leak

2006-01-03 Thread S. Alexander Jacobson

Joel,

In most cases, it just doesn't make sense to run 1000 threads 
simultaneously that are all bottlenecked on the same resource (e.g. 
CPU/memory) See e.g. http://www.eecs.harvard.edu/~mdw/proj/seda/


You should be grouping incoming events into queues by expected 
workload/event.  Then you can give the client fairly reliable 
information about how long it will have to wait based on the size of 
the queue on which event is waiting.


And if you have no way to differentiate between event workloads a 
priori then you really can't be giving clients response guarantees and 
need to rethink your business logic.


FYI: I actually created a Haskell application server based on this 
logic called HAppS (see http://happs.org) and am in the process of 
getting binaryIO added to it.


-Alex-

__
S. Alexander Jacobson tel:917-770-6565 http://alexjacobson.com






On Tue, 3 Jan 2006, Joel Reymont wrote:


Simon,

I don't think CPU usage is the issue. An individual thread will take a 
fraction of a second to deserialize a large packet. The issue is that, as you 
pointed out, you can get alerts even with 50 threads. Those fractions of a 
second add up in a certain way that's detrimental to the performance of the 
app.


The timeleak code uses Ptr Word8 to pickle which should be very efficient. I 
believe the delay comes from the way 'sequ' is compiled by GHC. I'll take the 
liberty of quoting Andrew Kennedy (your colleague from MS Research) who wrote 
the picklers:


--
My original pickler implementation was for SML. It was used in the MLj 
compiler, and is still used in the SML.NET compiler, and has acceptable 
performance (few ms pickling/unpickling for typical intermediate language 
object files). I must admit that I've not used the Haskell variant in anger. 
Apart from the inherent slowdown associated with laziness, is there a 
particular reason for poor performance?

--

'sequ' by itself does not seem like a big deal but when used to model records 
it builds a large nested lambda-list and I don't think that list is being 
compiled efficiently. I would appreciate if you could look at that and issue 
a verdict now that Andrew cofirms using the picklers in a real-life 
environment and w/o major problems.


Suppose I chose a different implementation of binary IO and disposed of 
pickler combinators.  Suppose I gained a 2x speed-up by doing so. I would now 
be getting alerts with 100 threads instead of 50, no? That's still far from 
ideal.


Joel

On Jan 3, 2006, at 4:43 PM, Simon Marlow wrote:

The reason things are the way they are is that a large number of *running* 
threads is not a workload we've optimised for.  In fact, Joel's program is 
the first one I've seen with a lot of running threads, apart from our 
testsuite.  And I suspect that when Joel uses a better binary I/O 
implementation a lot of that CPU usage will disappear.


--
http://wagerlabs.com/





___
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] How to print a string (lazily)

2006-01-03 Thread Tomasz Zielonka
On Tue, Jan 03, 2006 at 05:49:07PM +, Neil Mitchell wrote:
 All Haskell functions are lazy, hence there is no need to write a
 lazy version of your print_list function. I think the function you
 probably want is:
 
 putStr (unlines xs)
 
 This uses the bulid in unlines function, which is similar in spirit to
 join (you get more quotes, which I guess you don't want)
 
 The equivalent in monad'y programming is:
 
 mapM putStrLn xs
 
 The first one has fewer monads, so I prefer it, but take your pick :)

Nitpicking a bit to prevent possible confusion: a monad is a *type
constructor*, not an expression. In both variants above you are dealing
with two monads - IO and [] - however, the Monad instance for [] is
not used.

Best regards
Tomasz

-- 
I am searching for programmers who are good at least in
(Haskell || ML)  (Linux || FreeBSD || math)
for work in Warsaw, Poland
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Progress on shootout entries

2006-01-03 Thread Chris Kuklewicz
Hello,

  Where there were no entries to the
http://shootout.alioth.debian.org/benchmark.php?test=chameneoslang=all
benchmark, there are now two.  The one by Josh Goldfoot is already
posted, the one Einar Karttunen and I optimized has been submitted and
will run faster/smaller.  Our code is at
http://haskell.org/hawiki/ChameneosEntry

  Now for improving the fasta benchmark,
http://shootout.alioth.debian.org/benchmark.php?test=fastalang=all ,
which currently has a space leak in the Haskell entry.

  A non-leaking version which has been optimized to run 3.5 times faster
is now up at http://haskell.org/hawiki/FastaEntra (ooops..my spelling
mistake).

  It could still be made to run about 3 times faster, if the other
languages are any guide.  Anyone want to help polish this one?

 Also, two other existing entries have space leaks, as can be seen at
http://shootout.alioth.debian.org/benchmark.php?test=alllang=ghclang2=ghc

 And finially, the haskel entry for
http://shootout.alioth.debian.org/benchmark.php?test=fannkuchlang=all
 is currently the *slowest* entry out of 28 languages.  It is 813x
slower than the c-code, 500x slower than OCaml.  Should be easy to make
it faster...

Cheers,

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


Re: [Haskell-cafe] How to print a string (lazily)

2006-01-03 Thread Udo Stenzel
Daniel Carrera wrote:
 I've been studying more Haskell and I've improved a lot. But I just hit 
 a small problem. I want to print all the elements of a linst (putStr). 
 I'd like to write something like this:
 
 print_list [] = do putStr 

This looks as if you're confused.  The keyword do is completely
redundant.  do does not mean please ignore all rules and allow side
effects, it rather means please build a new action by sequencing what
follows.  So do with only one action after it is useless (and a sign
of confusion).  Have you ever heard about the command and composite
design patterns?  Well, in Haskell, you get them for free with monads.


 print_list (x:xs) = (do putStr x)  print_list xs

print_list (x:xs) = do putStr x ; print_list xs


 
 print_list xs = do putStr(join xs)
   where join [] = 
 join (x:xs) = (show x) ++ \n ++ join xs
 
 But the thing is, I want to write a lazy version of this function.

What's not lazy about it?  If you think, join has to complete before
putStr can be called, simply forget it.  Those words don't even make
sense in a lazy functional setting.


Udo.
-- 
Lost: gray and white female cat.  Answers to electric can opener.


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


Re: [Haskell-cafe] file i/o

2006-01-03 Thread Robert Heffernan
Neil and Thomas,

Thanks to both of you for your help.  I have things working now.

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


Re: [Haskell-cafe] Re: Joels Time Leak

2006-01-03 Thread Joel Reymont
The timeleak code is just a repro case. In real life I'm reading from  
sockets as opposed to a file.


All I'm trying to do is run poker bots. They talk to the server and  
play poker. Of course some events are more important than others, a  
request to make a bet is more important than, say, a table update. I  
do need to run as many poker bots as I can.


I think that my customer's goal of 4,000 bots is unattainable in a  
single app. It's probably possible per machine. Overall, I find this  
too complex to manage with Haskell as there are many factors that can  
contribute to my delays and timeouts. There are also quite a few  
unanswered questions at the moment (why is 'sequ' slow? does the  
scheduler need to be tuned?) that leave me scratching my head.


On Jan 3, 2006, at 9:17 PM, S. Alexander Jacobson wrote:

You should be grouping incoming events into queues by expected  
workload/event.  Then you can give the client fairly reliable  
information about how long it will have to wait based on the size  
of the queue on which event is waiting.


And if you have no way to differentiate between event workloads a  
priori then you really can't be giving clients response guarantees  
and need to rethink your business logic.


--
http://wagerlabs.com/





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


Re: [Haskell-cafe] RE: Haskell vs. Erlang: The scheduler

2006-01-03 Thread Tomasz Zielonka
On Tue, Jan 03, 2006 at 04:36:37PM -, Simon Marlow wrote:
  Is it impractical then to implement this type of app in Haskell?
  Based on the nature of Haskell scheduling I would be inclined to say
  yes.
 
 Absolutely not!
 
 Apart from the problem you have with a space leak caused by the input
 buffer of the logging thread overflowing, which is easily fixed by using
 a bounded channel, I don't know why you want priorities.  Is there
 something else?
 
 We could easily add Erlang-style priorities (though without the overhead
 of counting function calls, I'd do it by counting allocations), but I'd
 rather not if we can avoid it.

You could also achieve a similar effect without hacking the RTS, for
example: track the number of elements in a Chan and on writeChan invoke
yield with probability based on the number of elements in Chan - the
more elements the higher the probability. You could experiment with
different probability distributions.

This is assuming that yield will make the thread wait for the next
round.

Best regards
Tomasz

-- 
I am searching for programmers who are good at least in
(Haskell || ML)  (math || Linux || FreeBSD)
for work in Warsaw, Poland
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Progress on shootout entries

2006-01-03 Thread Sebastian Sylvan
On 1/3/06, Chris Kuklewicz [EMAIL PROTECTED] wrote:
 Hello,

   Where there were no entries to the
 http://shootout.alioth.debian.org/benchmark.php?test=chameneoslang=all
 benchmark, there are now two.  The one by Josh Goldfoot is already
 posted, the one Einar Karttunen and I optimized has been submitted and
 will run faster/smaller.  Our code is at
 http://haskell.org/hawiki/ChameneosEntry

   Now for improving the fasta benchmark,
 http://shootout.alioth.debian.org/benchmark.php?test=fastalang=all ,
 which currently has a space leak in the Haskell entry.

   A non-leaking version which has been optimized to run 3.5 times faster
 is now up at http://haskell.org/hawiki/FastaEntra (ooops..my spelling
 mistake).

   It could still be made to run about 3 times faster, if the other
 languages are any guide.  Anyone want to help polish this one?

  Also, two other existing entries have space leaks, as can be seen at
 http://shootout.alioth.debian.org/benchmark.php?test=alllang=ghclang2=ghc

  And finially, the haskel entry for
 http://shootout.alioth.debian.org/benchmark.php?test=fannkuchlang=all
  is currently the *slowest* entry out of 28 languages.  It is 813x
 slower than the c-code, 500x slower than OCaml.  Should be easy to make
 it faster...

While the implementation is far from nice it still finishes with N=9
(which, AFAICT, is what the benchmark is run with) in a fraction of a
second on my machine (and not anywhere near 51s as in the
benchmark)... I have a 2.6 Ghz P4...

I was going to rewrite it using mutable STArrays for a pure version
that's still fast but i sorta feel like I lost the motivation now that
it turns out the existing implementation, though ugly, performs
somewhat okay...

/S
--
Sebastian Sylvan
+46(0)736-818655
UIN: 44640862
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Progress on shootout entries

2006-01-03 Thread Sebastian Sylvan
On 1/3/06, Sebastian Sylvan [EMAIL PROTECTED] wrote:
 On 1/3/06, Chris Kuklewicz [EMAIL PROTECTED] wrote:
  Hello,
 
Where there were no entries to the
  http://shootout.alioth.debian.org/benchmark.php?test=chameneoslang=all
  benchmark, there are now two.  The one by Josh Goldfoot is already
  posted, the one Einar Karttunen and I optimized has been submitted and
  will run faster/smaller.  Our code is at
  http://haskell.org/hawiki/ChameneosEntry
 
Now for improving the fasta benchmark,
  http://shootout.alioth.debian.org/benchmark.php?test=fastalang=all ,
  which currently has a space leak in the Haskell entry.
 
A non-leaking version which has been optimized to run 3.5 times faster
  is now up at http://haskell.org/hawiki/FastaEntra (ooops..my spelling
  mistake).
 
It could still be made to run about 3 times faster, if the other
  languages are any guide.  Anyone want to help polish this one?
 
   Also, two other existing entries have space leaks, as can be seen at
  http://shootout.alioth.debian.org/benchmark.php?test=alllang=ghclang2=ghc
 
   And finially, the haskel entry for
  http://shootout.alioth.debian.org/benchmark.php?test=fannkuchlang=all
   is currently the *slowest* entry out of 28 languages.  It is 813x
  slower than the c-code, 500x slower than OCaml.  Should be easy to make
  it faster...

 While the implementation is far from nice it still finishes with N=9
 (which, AFAICT, is what the benchmark is run with) in a fraction of a
 second on my machine (and not anywhere near 51s as in the
 benchmark)... I have a 2.6 Ghz P4...

 I was going to rewrite it using mutable STArrays for a pure version
 that's still fast but i sorta feel like I lost the motivation now that
 it turns out the existing implementation, though ugly, performs
 somewhat okay...

Hmm.. This may be due to laziness. Since it's only supposed to print
out the first 30 lines it won't compute the full n! values...


/S


--
Sebastian Sylvan
+46(0)736-818655
UIN: 44640862
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] How to print a string (lazily)

2006-01-03 Thread Wolfgang Jeltsch
Am Dienstag, 3. Januar 2006 19:15 schrieb Daniel Carrera:
 Neil Mitchell wrote:
  All Haskell functions are lazy, hence there is no need to write a
  lazy version of your print_list function. I think the function you
  probably want is:
 
  putStr (unlines xs)

 Hhmm... that does work, and I'm a bit surprised that it does. I guess
 I'm still stuck in the eager computation mindset. I would expect putStr
 to have to wait for the (unlines xs) to be finished before doing any
 printing, but it doesn't.

(unlines xs) is only evaluated on demand.  Think of putStr as defined as 
follows:

putStr :: String - IO ()
putStr []
= return ()
putStr (x : xs)
= do
putChar x
putStr xs

Every character of the string is evaluated when it is needed by putChar x, not 
earlier.  So the argument of putStr is evaluated lazily.

 [...]

 Some day I'll get the hang of this lazy evaluation thing. :)

Yes. :-)  Lazy evaluation is really powerful. ;-)

  The first one has fewer monads, so I prefer it, but take your pick :)

 Monads scare me, so I'll pick the first :)  Thanks!

It is preferable because it does more of the work without imperative 
programming.

 Cheers,
 Daniel.

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


Re: [Haskell-cafe] Progress on shootout entries

2006-01-03 Thread Chris Kuklewicz
Discussing the fannkuch entry

Sebastian Sylvan wrote:
 On 1/3/06, Sebastian Sylvan [EMAIL PROTECTED] wrote:
 
On 1/3/06, Chris Kuklewicz [EMAIL PROTECTED] wrote:

Hello,

 And finially, the haskel entry for
http://shootout.alioth.debian.org/benchmark.php?test=fannkuchlang=all
 is currently the *slowest* entry out of 28 languages.  It is 813x
slower than the c-code, 500x slower than OCaml.  Should be easy to make
it faster...

While the implementation is far from nice it still finishes with N=9
(which, AFAICT, is what the benchmark is run with) in a fraction of a
second on my machine (and not anywhere near 51s as in the
benchmark)... I have a 2.6 Ghz P4...

I was going to rewrite it using mutable STArrays for a pure version
that's still fast but i sorta feel like I lost the motivation now that
it turns out the existing implementation, though ugly, performs
somewhat okay...
 
 
 Hmm.. This may be due to laziness. Since it's only supposed to print
 out the first 30 lines it won't compute the full n! values...
 
 
 /S

If you look at the code, then you may see that

 findmax :: Int8 - [[Int8]] - Int8
 findmax soFar [] = soFar
 findmax soFar (x:xs) =
max (flop 0 x) (findmax soFar xs)

is broken. The soFar parameter (which is originally 0) does absolutely
nothing.  I think this would be more appropriate:

findmax' xs = foldl1' max $ map (flop 0) xs

They use (!!) on lists instead of, as you said, STArrays.

For truly optimal performance mallocArray of Word8 would actually model
the c code much better than the lists.

They have [a] types and fromIntegral when it is all Int8, as far as I
can see.

And for sanity's sake, I wish one of the entries would have documentated
a clear way to understand the permutation generator.   The PHP and Lua
versions are almost legible.

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


Re: [Haskell-cafe] Progress on shootout entries

2006-01-03 Thread Cale Gibbard
On 03/01/06, Sebastian Sylvan [EMAIL PROTECTED] wrote:
 On 1/3/06, Sebastian Sylvan [EMAIL PROTECTED] wrote:
  On 1/3/06, Chris Kuklewicz [EMAIL PROTECTED] wrote:
   Hello,
  
 Where there were no entries to the
   http://shootout.alioth.debian.org/benchmark.php?test=chameneoslang=all
   benchmark, there are now two.  The one by Josh Goldfoot is already
   posted, the one Einar Karttunen and I optimized has been submitted and
   will run faster/smaller.  Our code is at
   http://haskell.org/hawiki/ChameneosEntry
  
 Now for improving the fasta benchmark,
   http://shootout.alioth.debian.org/benchmark.php?test=fastalang=all ,
   which currently has a space leak in the Haskell entry.
  
 A non-leaking version which has been optimized to run 3.5 times faster
   is now up at http://haskell.org/hawiki/FastaEntra (ooops..my spelling
   mistake).
  
 It could still be made to run about 3 times faster, if the other
   languages are any guide.  Anyone want to help polish this one?
  
Also, two other existing entries have space leaks, as can be seen at
   http://shootout.alioth.debian.org/benchmark.php?test=alllang=ghclang2=ghc
  
And finially, the haskel entry for
   http://shootout.alioth.debian.org/benchmark.php?test=fannkuchlang=all
is currently the *slowest* entry out of 28 languages.  It is 813x
   slower than the c-code, 500x slower than OCaml.  Should be easy to make
   it faster...
 
  While the implementation is far from nice it still finishes with N=9
  (which, AFAICT, is what the benchmark is run with) in a fraction of a
  second on my machine (and not anywhere near 51s as in the
  benchmark)... I have a 2.6 Ghz P4...
 
  I was going to rewrite it using mutable STArrays for a pure version
  that's still fast but i sorta feel like I lost the motivation now that
  it turns out the existing implementation, though ugly, performs
  somewhat okay...

 Hmm.. This may be due to laziness. Since it's only supposed to print
 out the first 30 lines it won't compute the full n! values...


 /S

You might not have been waiting for the final result. The first 30
perms print quickly, but it takes longer to get the solution to the
problem.

I managed to do better with the following program which gets the
following time report on my machine
real0m8.175s
user0m7.742s
sys 0m0.186s
as opposed to
real0m23.232s
user0m21.115s
sys 0m0.077s
for the shootout code.

I didn't try too hard to optimise it heavily, but it does use a
tree-based permutation generator I stole from some code which was in
an n-queens solution I had laying around (pretty sure it's not mine),
and an obvious memoisation hack when handling the flips.

 - Cale
import Data.Word
import Data.Array.Unboxed
import System.Environment

type Perm = Word8 - Word8

comparing p x y = compare (p x) (p y)

main = do [ns] - getArgs
  let n = read ns
  ps = perms n
  p = maximum $ map (flops n . perm) ps
  mapM (putStrLn . (= show)) (take 30 ps)
  putStrLn (Pfannkuchen( ++ ns ++ ) =  ++ (show p))


   -- NB. element subtree siblings! This is an n-ary tree
data Tree a = Node a (Tree a) (Tree a) | Empty

flop n f = fs `seq` \x - fs ! x
where fs :: UArray Word8 Word8
  fs = array (1,n) [(k, f' k) | k - [1..n]] 
  f' x =
if x = n
  then f (n-x+1)
  else f x
where n = f 1

flops n = length . (takeWhile ((/= 1) . ($ 1))) . (iterate (flop n))

showPerm n f = [1..n] = show . f

perm :: [Word8] - (Word8 - Word8)
perm [] n = n
perm (x:xs) 1 = x
perm (x:xs) n = perm xs (n-1)

paths depth t =  -- paths from the root of t to given depth
 let across d ancestors  Empty   rest = rest
 across d ancestors (Node e l r) rest =
down d (e:ancestors) l (across d ancestors r rest)
   
 down d ancestors t rest =
if d = depth then ancestors:rest
else across (d+1) ancestors t rest
 in across 1 [] t []

build n = 
 let
   t = toplevel n  

   toplevel m =
 if m  1 then Empty
 else Node m (f n m t) (toplevel (m-1))

   f col banned  Empty= Empty 
   f col banned (Node a subtree sibs) =
let others = f col banned sibs
in if banned == a then others
   else Node a (f (col-1) banned subtree) others
 in t

perms n = paths n (build n)

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


Re: [Haskell-cafe] Progress on shootout entries

2006-01-03 Thread Cale Gibbard
On 03/01/06, Cale Gibbard [EMAIL PROTECTED] wrote:
 I managed to do better with the following program which gets the
 following time report on my machine
 real0m8.175s
 user0m7.742s
 sys 0m0.186s
 as opposed to
 real0m23.232s
 user0m21.115s
 sys 0m0.077s
 for the shootout code.

 I didn't try too hard to optimise it heavily, but it does use a
 tree-based permutation generator I stole from some code which was in
 an n-queens solution I had laying around (pretty sure it's not mine),
 and an obvious memoisation hack when handling the flips.

Hmm, do the permutations have to be in their specific order? This
permutation generator seems to go through them in a somewhat different
order. It seems irrelevant to the problem, but since they want the
permutations as part of the output, it's a good question. :) In that
case, I wonder if it would be best to use some other generator to
print the first 30, then switch to some faster generator for the
actual computation. :)

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


Re: [Haskell-cafe] Progress on shootout entries

2006-01-03 Thread Iavor Diatchki
Hello,
Here is a short (16 lines) and readable Haskell'98 solution.
I haven't optimized it or tested it much.
When compiled with ghc(6.4.1) -O2, it takes about 10s to compute the
answer for 9,
on my P3 366MHz machine.  It seems to use about 16K of memory.
-Iavor

import System(getArgs)

flop xs@(x:_) = reverse (take x xs) ++ drop x xs
flops xs  = takeWhile ((1 /=) . head) (iterate flop xs)

perms xs  = foldr (concatMap . ins) [[]] xs

ins x []  = [[x]]
ins x (y:ys)  = (x:y:ys) : map (y:) (ins x ys)

pfannkuchen x = maximum (map (length . flops) (perms [1..x]))

main  = do a:_ - getArgs
   let n = read a :: Int
   putStrLn (unlines (map show (take 30 (perms [1..n]
   print (pfannkuchen n)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Progress on shootout entries

2006-01-03 Thread Kimberley Burchett
I took a quick crack at optimizing fannkuch.hs.  I got it down from 33s to 
1.25s on my machine, with N=9.  That should put it between forth and 
ocaml(bytecode) in the shootout page.  The main changes I made were using 
Int instead of Int8, foldl' to accumulate the max number of folds, a 
custom flop function rather than a combination of reverse and splitAt, and 
a simpler definition for permutations.


   http://kimbly.com/code/fannkuch.hs

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


Re: [Haskell-cafe] Progress on shootout entries

2006-01-03 Thread Sebastian Sylvan
On 1/3/06, Chris Kuklewicz [EMAIL PROTECTED] wrote:
 Hello,

   Where there were no entries to the
 http://shootout.alioth.debian.org/benchmark.php?test=chameneoslang=all
 benchmark, there are now two.  The one by Josh Goldfoot is already
 posted, the one Einar Karttunen and I optimized has been submitted and
 will run faster/smaller.  Our code is at
 http://haskell.org/hawiki/ChameneosEntry

   Now for improving the fasta benchmark,
 http://shootout.alioth.debian.org/benchmark.php?test=fastalang=all ,
 which currently has a space leak in the Haskell entry.

   A non-leaking version which has been optimized to run 3.5 times faster
 is now up at http://haskell.org/hawiki/FastaEntra (ooops..my spelling
 mistake).

   It could still be made to run about 3 times faster, if the other
 languages are any guide.  Anyone want to help polish this one?

  Also, two other existing entries have space leaks, as can be seen at
 http://shootout.alioth.debian.org/benchmark.php?test=alllang=ghclang2=ghc

I took a stab at the rev-comp one due to boredom. It's not a space
leak, believe it or not, it's *by design*...

My god, I think someone is consciously trying to sabotage Haskell's reputation!

Instead of reading input line-by-line and doing the computation, it
reads a whole bunch of lines (hundreds of megs worth, apparently) and
only does away with them when a new header appears.

Anyway, I uploaded a dead simple first-naive-implementation which is
significantly faster (and more elegant):

complement i = complArr ! i'
 where i' = toUpper i

complArr = array ('A','Z') (self ++ complAssoc)
   where self = az `zip` az
 az = ['A'..'Z']
complAssoc = [
  
('A','T'),('C','G'),('G','C'),('T','A'),('U','A'),('M','K'),('R','Y'),('W','W'),
  
('S','S'),('Y','R'),('K','M'),('V','B'),('D','H'),('D','H'),('B','V'),('N','N')
 ]

process header@('':xs) = putStrLn header
process x = putStrLn (map complement x)

main = do xs - getContents
   mapM process (lines xs)




/S
--
Sebastian Sylvan
+46(0)736-818655
UIN: 44640862
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Project postmortem II /Haskell vs. Erlang/

2006-01-03 Thread Dylan Thurston
On Sun, Jan 01, 2006 at 11:12:31PM +, Joel Reymont wrote:
 Simon,
 
 Please see this post for an extended reply:
 
 http://wagerlabs.com/articles/2006/01/01/haskell-vs-erlang-reloaded

Looking at this code, I wonder if there are better ways to express
what you really want using static typing.  To wit, with records, you
give an example


data Pot = Pot
{
 pProfit :: !Word64,
 pAmounts :: ![Word64] -- Word16/
} deriving (Show, Typeable)

mkPot :: Pot
mkPot =
Pot
{
 pProfit = 333,
 pAmounts = []
}

and complain about having to explain to the customer how xyFoo is
really different from zFoo when they really mean the same thing.  I
wonder: if they really are the same thing, is there a way to get the
data types to faithfully reflect that?  Can you post a few more
snippets of your data structures?

Peace,
Dylan


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


Re: [Haskell-cafe] Progress on shootout entries

2006-01-03 Thread Dylan Thurston
On Wed, Jan 04, 2006 at 03:02:29AM +0100, Sebastian Sylvan wrote:
 I took a stab at the rev-comp one due to boredom. It's not a space
 leak, believe it or not, it's *by design*...
 
 My god, I think someone is consciously trying to sabotage Haskell's 
 reputation!
 
 Instead of reading input line-by-line and doing the computation, it
 reads a whole bunch of lines (hundreds of megs worth, apparently) and
 only does away with them when a new header appears.
 
 Anyway, I uploaded a dead simple first-naive-implementation which is
 significantly faster (and more elegant):
 ...

The program is supposed to do reverse and complement.  The code you
posted just does complement.

Peace,
Dylan


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


Re: [Haskell-cafe] Progress on shootout entries

2006-01-03 Thread Sebastian Sylvan
On 1/4/06, Sebastian Sylvan [EMAIL PROTECTED] wrote:
 On 1/3/06, Chris Kuklewicz [EMAIL PROTECTED] wrote:
  Hello,
 
Where there were no entries to the
  http://shootout.alioth.debian.org/benchmark.php?test=chameneoslang=all
  benchmark, there are now two.  The one by Josh Goldfoot is already
  posted, the one Einar Karttunen and I optimized has been submitted and
  will run faster/smaller.  Our code is at
  http://haskell.org/hawiki/ChameneosEntry
 
Now for improving the fasta benchmark,
  http://shootout.alioth.debian.org/benchmark.php?test=fastalang=all ,
  which currently has a space leak in the Haskell entry.
 
A non-leaking version which has been optimized to run 3.5 times faster
  is now up at http://haskell.org/hawiki/FastaEntra (ooops..my spelling
  mistake).
 
It could still be made to run about 3 times faster, if the other
  languages are any guide.  Anyone want to help polish this one?
 
   Also, two other existing entries have space leaks, as can be seen at
  http://shootout.alioth.debian.org/benchmark.php?test=alllang=ghclang2=ghc

 I took a stab at the rev-comp one due to boredom. It's not a space
 leak, believe it or not, it's *by design*...

 My god, I think someone is consciously trying to sabotage Haskell's 
 reputation!

 Instead of reading input line-by-line and doing the computation, it
 reads a whole bunch of lines (hundreds of megs worth, apparently) and
 only does away with them when a new header appears.

 Anyway, I uploaded a dead simple first-naive-implementation which is
 significantly faster (and more elegant):

 complement i = complArr ! i'
  where i' = toUpper i

 complArr = array ('A','Z') (self ++ complAssoc)
where self = az `zip` az
  az = ['A'..'Z']
 complAssoc = [
   
 ('A','T'),('C','G'),('G','C'),('T','A'),('U','A'),('M','K'),('R','Y'),('W','W'),
   
 ('S','S'),('Y','R'),('K','M'),('V','B'),('D','H'),('D','H'),('B','V'),('N','N')
  ]

 process header@('':xs) = putStrLn header
 process x = putStrLn (map complement x)

 main = do xs - getContents
mapM process (lines xs)


Oops! Apologies to whoever wrote the orignal version! Apparently I
didn't read the spec carefully enough, the sequences are supposed to
be reversed, which is why simply writing one line at a time doesn't
work.

/S

--
Sebastian Sylvan
+46(0)736-818655
UIN: 44640862
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Progress on shootout entries

2006-01-03 Thread Josh Goldfoot
Keep in mind that the shootout requires that the first 30 permutations printed 
out by the Fannkuch benchmark to be exactly those given in the example.  Any 
other order of permutations gets your code labeled Error by the shootout 
administrators.  See the discussion here:

http://alioth.debian.org/tracker/index.php?func=detailaid=302527group_id=30402atid=411646

The version of Fannkuch on the site before I got there used a permutation 
function that did not comply with this requirement.  My only contribution was 
to translate the acceptable algorithm into Haskell.  (The inefficient flop 
stuff and the other errors were not my fault, I swear!)  The resulting (slow) 
code can definitely be sped up, but unfortunately the shootout benchmark favors 
imperative languages (and impure functional languages, I guess).

I suppose we could have two permutation-generating functions:  One used only to 
generate the first 30 required by the benchmark, and another that is actually 
used to calculate the fannkuch value.  It's not clear how the shootout 
rule-lawyers would look that.  It seems to violate the same way rule.

I was able to significantly speed up the code by replacing the flip function 
with a function that relies entirely on pattern matching (no splitAts or 
reverses).  It looks ugly, though:

mangle list@(1:xs) = list
mangle (2:x2:xs) = x2:2:xs
mangle (3:x2:x3:xs) = x3:x2:3:xs
... and so on.


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


Re: [Haskell-cafe] Re: Progress on shootout entries

2006-01-03 Thread Jan-Willem Maessen

I was surprised to learn that indexed insertion:

permutations (x:xs) =
[insertAt n x perms | perms - permutations xs,
  n - [0..length xs] ]

insertAt :: Int - a - [a] - [a]
insertAt 0 y xs = y:xs
insertAt n y (x:xs) = x:(insertAt (n-1) y xs)

was faster than the usual version of permutation based on inserts:

permutations (x:xs) =
[insertAt n x perms | perms - permutations xs,
  n - [0..length xs] ]
insertAt 0 y xs = y:xs
insertAt n y (x:xs) = x:(insertAt (n-1) y xs)

However, try these on for size.  The non-strict flop, which  
traverses its input exactly once, is the most surprising and made by  
far the biggest difference:



findmax :: [[Int]] - Int
findmax xss = fm xss 0
  where fm [] mx = mx
fm (p:ps) mx = fm ps $! (countFlops p `max` mx)

countFlops :: [Int] - Int
countFlops as = cf as 0
  where cf(1:_) flops = flops
cf xs@(x:_) flops = cf (flop x xs) $! (flops+1)

flop :: Int - [Int] - [Int]
flop n xs = rs
  where (rs,ys) = fl n xs ys
fl 0 xs ys = (ys, xs)
fl n (x:xs) ys = fl (n-1) xs (x:ys)


On Jan 3, 2006, at 8:01 PM, Kimberley Burchett wrote:

I took a quick crack at optimizing fannkuch.hs.  I got it down from  
33s to 1.25s on my machine, with N=9.  That should put it between  
forth and ocaml(bytecode) in the shootout page.  The main changes I  
made were using Int instead of Int8, foldl' to accumulate the max  
number of folds, a custom flop function rather than a combination  
of reverse and splitAt, and a simpler definition for permutations.


   http://kimbly.com/code/fannkuch.hs

Kimberley Burchett
___
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] How to print a string (lazily)

2006-01-03 Thread Tomasz Zielonka
On Tue, Jan 03, 2006 at 10:28:54PM +0100, Udo Stenzel wrote:
 Daniel Carrera wrote:
  print_list [] = do putStr 
 
 This looks as if you're confused.  The keyword do is completely
 redundant.  do does not mean please ignore all rules and allow side
 effects, it rather means please build a new action by sequencing what
 follows.  So do with only one action after it is useless (and a sign
 of confusion).

Perhaps you are right, but this can also be a sign of version-control
awareness, and I know Daniel uses darcs.

I often place a single command in a do-block, because I want future
changes to touch as little lines as possible. Consider:

f = putStrLn b

and

f = do
putStrLn b

If you'll later add more commands, you'll get something like:

f = do
x - g
putStrLn b
putStrLn x

which is much closer to the reduntant-do variant.

Best regards
Tomasz

-- 
I am searching for programmers who are good at least in
(Haskell || ML)  (Linux || FreeBSD || math)
for work in Warsaw, Poland
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] How to print a string (lazily)

2006-01-03 Thread Glynn Clements

Donn Cave wrote:

  I sometimes call a function with side-effects in IO a command.  But
  the terms are fungible.  But calling putStr a function is correct.  It
  is not a pure function however.
 
 Is that the standard party line?  I mean, we all know its type and
 semantics, whatever you want to call them, but if we want to put names
 to things, I had the impression that the IO monad is designed to work
 in a pure functional language - so that the functions are indeed actually
 pure, including putStr.

putStr is a pure function, but it isn't a pure function ;)

OTOH, getLine isn't even a function, just a value.

-- 
Glynn Clements [EMAIL PROTECTED]
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe