[Haskell-cafe] Re: sendfile leaking descriptors on Linux?

2010-02-06 Thread Bardur Arantsson

Brandon S. Allbery KF8NH wrote:

On Feb 5, 2010, at 02:56 , Bardur Arantsson wrote:

[--snip--]


Broken pipe is normally handled as a signal, and is only mapped to an 
error if SIGPIPE is set to SIG_IGN.  I can well imagine that the SIGPIPE 
signal handler isn't closing resources properly; a workaround would be 
to use the System.Posix.Signals API to ignore SIGPIPE, but I don't know 
if that would work as a general solution (it would depend on what other 
uses of pipes/sockets exist).


It was a good idea, but it doesn't seem to help to add

installHandler sigPIPE Ignore (Just fullSignalSet)

to the main function. (Given the package name I assume 
System.Posix.Signals works similarly to regular old signals, i.e. 
globally per-process.)


This is really starting to drive me round the bend...

One further thing I've noticed: When compiling on my 64-bit machine,
ghc issues the following warnings:

Linux.hsc:41: warning: format ‘%d’ expects type ‘int’, but argument 3 
has type ‘long unsigned int’
Linux.hsc:45: warning: format ‘%d’ expects type ‘int’, but argument 3 
has type ‘long unsigned int’
Linux.hsc:45: warning: format ‘%d’ expects type ‘int’, but argument 3 
has type ‘long unsigned int’
Linux.hsc:45: warning: format ‘%d’ expects type ‘int’, but argument 3 
has type ‘long unsigned int’


Those lines are:

39: -- max num of bytes in one send
40: maxBytes :: Int64
41: maxBytes = fromIntegral (maxBound :: (#type ssize_t))

and

44: foreign import ccall unsafe sendfile64 c_sendfile
45:   :: Fd - Fd - Ptr (#type off_t) - (#type size_t) - IO (#type 
ssize_t)



This looks like a typical 32/64-bit problem, but normally I would expect 
any real run-time problems caused by a problematic conversion in the FFI 
to crash the whole process. Maybe I'm wrong about this...


Cheers,

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


Re: [Haskell-cafe] a beginner question: decorate-op-undecorate

2010-02-06 Thread Stephen Tetley
Hello Aran

Changing to an explicit sum type rather than using Either might
subsequent functions that process a Binding cleaner:

data Binding = BoundVar  Var Value
 | PossiblyBound Var [Value]

Naturally you might want to consider a better constructor name than
'PossiblyBound'.

-- 

As an open question to the list - the above change can be seen as a
'denormalisation' of the data type (adding redundancy), does anyone
know of a reference that covers such things?

The only thing I can think of close is David S. Wile's Abstract
syntax from concrete syntax...

Thanks

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


Re: [Haskell-cafe] cabal fun (not)

2010-02-06 Thread Peter Robinson
On 6 February 2010 03:33, Ivan Miljenovic ivan.miljeno...@gmail.com wrote:
 If you upgrade a library, it will break all other libraries that
 depend upon it.  ghc-pkg list will tell you which libraries are
 broken and need to be rebuilt.

I think you mean ghc-pkg check.

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


Re: [Haskell-cafe] cabal fun (not)

2010-02-06 Thread Ivan Miljenovic
On 6 February 2010 19:23, Peter Robinson thaldy...@gmail.com wrote:
 I think you mean ghc-pkg check.

Yes, I do.  Whoops :s



-- 
Ivan Lazar Miljenovic
ivan.miljeno...@gmail.com
IvanMiljenovic.wordpress.com
Charles de Gaulle  - The better I get to know men, the more I find
myself loving dogs. -
http://www.brainyquote.com/quotes/authors/c/charles_de_gaulle.html
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Simulation of interconnect network

2010-02-06 Thread Serguey Zefirov
2010/2/5 Roger King rogerking...@yahoo.com:
 I am building a simulator for an interconnect network for a multiprocessor 
 computer.  I would like to develop it in Haskell as an opportunity to learn 
 Haskell.

 The network will have a number of routers with input ports and output ports 
 and crossbars between them.  I would like to simulate the protocol.  This 
 would be an event driven simulator.  It would be at a high level, leaving out 
 many details.  I would like it to be fast and be able to run it on several 
 processors.

Crossbar is certainly easier using lazy lists of events.

Like those used in Hawk: http://eprints.kfupm.edu.sa/66296/1/66296.pdf

Event-driven approach is good for asynchronous behaviour, like
combinatorial logic etc. For single-clock clocked logic (and crossbar
is certainly that  kind of device) lazy lists are simpler to write and
reason about.

 I would like to know if you have any advice.  Has anyone done this before?  
 Are there any discrete event simulators written in Haskell?

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


Re: [Haskell-cafe] safe lazy IO or Iteratee?

2010-02-06 Thread John Lato
I've put my benchmarking code online at:

http://inmachina.net/~jwlato/haskell/research-iteratee.tar.bz2

unpack it so you have this directory structure:

./iteratee
./research-iteratee/

Also download my criterionProcessor programs.  The darcs repo is at

http://inmachina.net/~jwlato/haskell/criterionProcessor/

to use it, go into the criterionProcessor directory, edit the
testrunner.hs script for your environment, and run it.  This runs all
the benchmarks.  Then you can use the CritProc program (build with
cabal) to generate pictures.  I'm pretty sure you need Chart HEAD in
order to build CritProc (I hacked my Chart install, but I think the
only important change has been applied to HEAD).

I make no guarantees that these will all build properly, it's
basically a work-in-progress dump.

John


On Fri, Feb 5, 2010 at 10:25 PM, John Millikin jmilli...@gmail.com wrote:
 Benchmark attached. It just enumerates a list until EOF is reached.

 An interesting thing I've noticed is that IterateeMCPS performs better
 with no optimization, but -O2 gives IterateeM the advantage. Their
 relative performance depends heavily on the chunk size -- for example,
 CPS is much faster at chunk size 1, but slower with 100-element
 chunks.

 On Fri, Feb 5, 2010 at 08:56, John Lato jwl...@gmail.com wrote:
 On Fri, Feb 5, 2010 at 4:31 PM, Valery V. Vorotyntsev
 valery...@gmail.com wrote:
 John Lato jwl...@gmail.com wrote:

 Both designs appear to offer similar performance in aggregate,
 although there are differences for particular functions.  I haven't
 yet had a chance to test the performance of the CPS variant, although
 Oleg has indicated he expects it will be higher.

 @jwlato:
 Do you mind creating `IterateeCPS' tree in
 http://inmachina.net/~jwlato/haskell/iteratee/src/Data/, so we can
 start writing CPS performance testing code?

 I'm working on the CPS version and will make it public when it's done.
  It may take a week or so; this term started at 90 and has picked up.
 I have several benchmark sources that aren't public yet, but I can put
 them online for your perusal.


 AFAICS, you have benchmarks for IterateeM-driven code already:
 http://inmachina.net/~jwlato/haskell/iteratee/tests/benchmarks.hs

 Those will make more sense when I've added the context of the
 codebases in use.  There are several more sets of output that I simply
 haven't published yet, including bytestring-based variants.


 John Millikin jmilli...@gmail.com wrote:

 I wrote some criterion benchmarks for IterateeM vs IterateeCPS, and
 the CPS version was notably slower. I don't understand enough about
 CPS to diagnose why, but the additional runtime was present in even
 simple cases (reading from a file, writing back out).

 That's very interesting.  I wonder if I'll see the same, and if I'd be
 able to figure it out myself...

 Did you benchmark any cases without doing IO?  Sometimes the cost of
 the IO can overwhelm any other measurable differences, and also disk
 caching can affect results.  Criterion should highlight any major
 outliers, but I still like to avoid IO when benchmarking unless
 strictly necessary.


 @jmillikin:
 Could you please publish those benchmarks?

 +1

 John


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


Re: [Haskell-cafe] Re: sendfile leaking descriptors on Linux?

2010-02-06 Thread Felipe Lessa
On Sat, Feb 06, 2010 at 09:16:35AM +0100, Bardur Arantsson wrote:
 Brandon S. Allbery KF8NH wrote:
 On Feb 5, 2010, at 02:56 , Bardur Arantsson wrote:
 [--snip--]
 
 Broken pipe is normally handled as a signal, and is only mapped
 to an error if SIGPIPE is set to SIG_IGN.  I can well imagine that
 the SIGPIPE signal handler isn't closing resources properly; a
 workaround would be to use the System.Posix.Signals API to ignore
 SIGPIPE, but I don't know if that would work as a general solution
 (it would depend on what other uses of pipes/sockets exist).

 It was a good idea, but it doesn't seem to help to add

   installHandler sigPIPE Ignore (Just fullSignalSet)

 to the main function. (Given the package name I assume
 System.Posix.Signals works similarly to regular old signals, i.e.
 globally per-process.)

 This is really starting to drive me round the bend...

Have you seen GHC ticket #1619?

http://hackage.haskell.org/trac/ghc/ticket/1619


 One further thing I've noticed: When compiling on my 64-bit machine,
 ghc issues the following warnings:

 Linux.hsc:41: warning: format ‘%d’ expects type ‘int’, but argument
 3 has type ‘long unsigned int’
 Linux.hsc:45: warning: format ‘%d’ expects type ‘int’, but argument
 3 has type ‘long unsigned int’
 Linux.hsc:45: warning: format ‘%d’ expects type ‘int’, but argument
 3 has type ‘long unsigned int’
 Linux.hsc:45: warning: format ‘%d’ expects type ‘int’, but argument
 3 has type ‘long unsigned int’

 Those lines are:

 39: -- max num of bytes in one send
 40: maxBytes :: Int64
 41: maxBytes = fromIntegral (maxBound :: (#type ssize_t))

 and

 44: foreign import ccall unsafe sendfile64 c_sendfile
 45:   :: Fd - Fd - Ptr (#type off_t) - (#type size_t) - IO
 (#type ssize_t)

 This looks like a typical 32/64-bit problem, but normally I would
 expect any real run-time problems caused by a problematic conversion
 in the FFI to crash the whole process. Maybe I'm wrong about this...

To convert those '#' constants, hsc2hs preprocessor constructs a
C file things like 'printf(%d, sizeof(ssize_t))' to use the
system's C compiler and avoid having the encode the ABI of every
platform (to be able to know the memory layout of the
structures).

So that message comes from that C file, not from your Haskell
one.  At runtime it really doesn't matter.

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


[Haskell-cafe] Using ShowS or Difference Lists

2010-02-06 Thread Mark Spezzano
Hi, 

Just wondering whether I can use ShowS or tupling or Difference Lists to speed 
up the following code?

It's basic text processing. It takes in a list of Lines where each Line is a 
list of Words and intersperses   between them then concatenates them into a 
longer String. Note that there is a recursive call and the ++ operator.

Thanks

Mark


-- Function: joinLines
-- Joins the Words within Lines together with whitespace and newline characters
-- Argument: Lines to pad with whitespace and newlines
-- Evaluate: The processed and concatenated String   
joinLines :: [Line] - String 
joinLines (l:[]) = concat (intersperse   l) 
joinLines (l:ls) = (concat (intersperse   l)) ++ ('\n':joinLines ls)

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


Re: [Haskell-cafe] a beginner question: decorate-op-undecorate

2010-02-06 Thread John Lato
 From: Aran Donohue aran.dono...@gmail.com

 Hi Haskell-Cafe,

 Consider a data type such as

 data Binding = Binding Var (Either Value [Value])

 representing a variable bound either to a fixed value or that has a list of
 possible values.

 I'd like to perform an operation on say, the fixed-value members of a list
 of bindings. Data.Either has partitionEithers---I'd essentially like to
 use partitionEithers, but in a way that it peeks into the value field of
 the binding. For the sake of argument, let's say I can't or can't modify
 Binding to move the Either to the outside.

I think that partitionEithers is leading you down the wrong trail.  If
what you want to do is modify some values inside the binding, I would
start with this:

 mapVal :: (Either Value [Value] - Either Value [Value]) - Binding - Binding
 mapVal f (Binding v e) = Binding v (f e)

 mapLeft :: (a - b) - Either a c - Either b c
 mapLeft f = either (Left . f) Right

 -- mapRight is just fmap, but for symmetry
 mapRight :: (b - c) - Either a b - Either a c
 mapRight = fmap

 modifyFixed :: (Value - Value) - Binding - Binding
 modifyFixed f b = mapVal (mapLeft f) b

 modifyList :: ([Value] - [Value]) - Binding - Binding
 modifyList f b = mapVal (mapRight f) b

 -- note that modifyFixed and modifyList have very nice point-free 
 representations
 -- modifyFixed = mapVal . mapLeft
 -- modifyList = mapVal . mapRight

Now to apply this to a list:

 modifyFixedBindings :: (Value - Value) - [Binding] - [Binding]
 modifyFixedBindings f binds = map (modifyFixed f) binds
 -- or point-free
 modifyFixedBindings' = map . modifyFixed

In my opinion, this would be more idiomatic if Binding were polymorphic:

 data Binding' k v = Binding' k v

 instance Functor (Binding' k) where
   fmap f (Binding' k v) = Binding' k (f v)

 type Binding2 = Binding' Var (Either Value [Value])

now mapVal is just fmap, and these functions are:

 modifyFixed2 :: (Val - Val) - [Binding2] - [Binding2]
 modifyFixed2 = fmap . fmap . mapLeft

 modifyList2 :: ([Val] - [Val]) - [Binding2] - [Binding2]
 modifyList2 = fmap . fmap . mapRight


I've typed out all the steps for clarity, but to be honest, I wouldn't
bother with the Fixed and List variants, unless you're going to use
them frequently.  I would do just:

 mapVals :: (Either Value [Value] - Either Value [Value]) - [Binding] - 
 [Binding]
 mapVals f = map (\(Binding var val) - Binding var (f val))

and leave it at that, using mapVals with the either function when
necessary.  I would consider making Binding polymorphic, though, so
you can write the Functor instance.

You may also want to look at Data.Traversable.

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


Re: [Haskell-cafe] Using ShowS or Difference Lists

2010-02-06 Thread Holger Siegel
Am Samstag, den 06.02.2010, 23:12 +1030 schrieb Mark Spezzano:
 Hi, 
 
 Just wondering whether I can use ShowS or tupling or Difference Lists to 
 speed up the following code?
 
 It's basic text processing. It takes in a list of Lines where each Line
  is a list of Words and intersperses   between them then concatenates
  them into a longer String. Note that there is a recursive call and the
  ++ operator.
 
 Thanks
 
 Mark
 
 
 -- Function: joinLines
 -- Joins the Words within Lines together with whitespace and newline 
 characters
 -- Argument: Lines to pad with whitespace and newlines
 -- Evaluate: The processed and concatenated String   
 joinLines :: [Line] - String 
 joinLines (l:[]) = concat (intersperse   l) 
 joinLines (l:ls) = (concat (intersperse   l)) ++ ('\n':joinLines ls)

You should use the existing library functions and leave the
optimisations to their implementor:

import Data.List

joinLines :: [[String]] - String
joinLines = intercalate \n . map (intercalate  )

Now you can easily switch to the faster ByteString library by simply
changing the import statement.


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


Re: [Haskell-cafe] Using ShowS or Difference Lists

2010-02-06 Thread Felipe Lessa
On Sat, Feb 06, 2010 at 11:12:40PM +1030, Mark Spezzano wrote:
 -- Function: joinLines
 -- Joins the Words within Lines together with whitespace and newline 
 characters
 -- Argument: Lines to pad with whitespace and newlines
 -- Evaluate: The processed and concatenated String
 joinLines :: [Line] - String
 joinLines (l:[]) = concat (intersperse   l)
 joinLines (l:ls) = (concat (intersperse   l)) ++ ('\n':joinLines ls)

Why not just

  joinLines = unlines . map unwords

This should be as fast as you may get using lists of lists of
lists of Chars :).

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


Re: [Haskell-cafe] a beginner question: decorate-op-undecorate

2010-02-06 Thread Stephen Tetley
Hi John

I'm not sure about making Binding polymorphic to get Functor,
Traversable, Foldable...

While I think you're correct that partitionEithers might not be a
useful example to draw from in this case, I'd assume that Binding
would be part of a larger syntax-tree, thus there might not be a
appropriate single leaf to make the tree polymorphic on. Felipe
Lessa's point - to use Uniplate or one of the Generics packages -
might be a better candidate for implementing traversals.

Best wishes

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


Re: [Haskell-cafe] Using ShowS or Difference Lists

2010-02-06 Thread Daniel Fischer
Am Samstag 06 Februar 2010 13:42:40 schrieb Mark Spezzano:
 Hi,

 Just wondering whether I can use ShowS or tupling or Difference Lists to
 speed up the following code?

 It's basic text processing. It takes in a list of Lines where each Line
 is a list of Words and intersperses   between them then concatenates
 them into a longer String. Note that there is a recursive call and the
 ++ operator.

 Thanks

 Mark


 -- Function: joinLines
 -- Joins the Words within Lines together with whitespace and newline
 characters -- Argument: Lines to pad with whitespace and newlines
 -- Evaluate: The processed and concatenated String
 joinLines :: [Line] - String
 joinLines (l:[]) = concat (intersperse   l)
 joinLines (l:ls) = (concat (intersperse   l)) ++ ('\n':joinLines ls)


joinLines = init . unlines . map unwords
joinLines = concat . intersperse \n . map unwords
joinLines = intercalate \n . map unwords
joinLines = intercalate \n . map (intercalate  )

it should be pretty good already, if that's a performance bottleneck, you 
might need to switch to (Lazy) ByteStrings. I don't think ShowS or 
difference lists would be any faster.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: cabal fun (not)

2010-02-06 Thread Johann Höchtl


On Feb 6, 3:33 am, Ivan Miljenovic ivan.miljeno...@gmail.com wrote:
 On 6 February 2010 01:05, Johannes Waldmann

 waldm...@imn.htwk-leipzig.de wrote:
  so please please please have cabal install fail with some error
  message if (that is, before) the install would break anything. - J.

 If you upgrade a library, it will break all other libraries that
 depend upon it.  ghc-pkg list will tell you which libraries are
 broken and need to be rebuilt.


Yes, I think that's the current behaviour what Johannes described yet
he suggest this to be sub-optimal. A warning about breakage would be
good before the breakage has happened.

 --
 Ivan Lazar Miljenovic
 ivan.miljeno...@gmail.com
 IvanMiljenovic.wordpress.com
 Joan Crawford  - I, Joan Crawford, I believe in the dollar.
 Everything I earn, I spend. 
 -http://www.brainyquote.com/quotes/authors/j/joan_crawford.html
 ___
 Haskell-Cafe mailing list
 haskell-c...@haskell.orghttp://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: sendfile leaking descriptors on Linux?

2010-02-06 Thread Bardur Arantsson

Felipe Lessa wrote:

On Sat, Feb 06, 2010 at 09:16:35AM +0100, Bardur Arantsson wrote:

Brandon S. Allbery KF8NH wrote:

On Feb 5, 2010, at 02:56 , Bardur Arantsson wrote:

[--snip--]

Broken pipe is normally handled as a signal, and is only mapped
to an error if SIGPIPE is set to SIG_IGN.  I can well imagine that
the SIGPIPE signal handler isn't closing resources properly; a
workaround would be to use the System.Posix.Signals API to ignore
SIGPIPE, but I don't know if that would work as a general solution
(it would depend on what other uses of pipes/sockets exist).

It was a good idea, but it doesn't seem to help to add

installHandler sigPIPE Ignore (Just fullSignalSet)

to the main function. (Given the package name I assume
System.Posix.Signals works similarly to regular old signals, i.e.
globally per-process.)

This is really starting to drive me round the bend...


Have you seen GHC ticket #1619?

http://hackage.haskell.org/trac/ghc/ticket/1619




I hadn't. I guess the conclusion is that SIG_PIPE is ignored by default anyway. 
So much
for that.

During yet another bout of debugging, I've added even more I am here 
instrumentation
code to the SendFile code, and the culprit seems to be threadWaitWrite. Here's 
the bit
of code I've modified:

 sendfile :: Fd - Fd - Ptr Int64 - Int64 - IO Int64
 sendfile out_fd in_fd poff bytes = do
 putStrLn PRE-threadWaitWrite
 threadWaitWrite out_fd
 putStrLn AFTER threadWaitWrite
 sbytes - c_sendfile out_fd in_fd poff (fromIntegral bytes)
 putStrLn $ AFTER c_sendfile; result was:  ++ (show sbytes)
 if sbytes = -1
   then do errno - getErrno
   if errno == eAGAIN
 then sendfile out_fd in_fd poff bytes
 else throwErrno Network.Socket.SendFile.Linux
   else return (fromIntegral sbytes)

This is the output when a file descriptor is lost:

---
AFTER sendfile: sbytes=27512
DIFFERENCE: 627264520
remaining=627264520, bytes=627264520
PRE-threadWaitWrite
Got request for CONTENT for objectId=1700,f2150400
Serving file 'X'...
Sending 625838080 bytes...
in_fd=13
---

So I have to conclude that threadWaitWrite is doing *something* which causes
the thread to die when the PS3 kills the connection.


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


[Haskell-cafe] Re: Category Theory woes

2010-02-06 Thread Benjamin L. Russell
On Tue, 02 Feb 2010 09:16:03 -0800, Creighton Hogg wrote:

 2010/2/2 Álvaro García Pérez agar...@babel.ls.fi.upm.es
 
 You may try Pierce's Basic Category Theory for Computer Scientists or
 Awodey's Category Theory, whose style is rather introductory. Both of them
 (I think) have a chapter about functors where they explain the Hom functor
 and related topics.

 
 I think Awodey's book is pretty fantastic, actually, but I'd avoid Pierce.
  Unlike Types and Programming Languages, I think Basic Category
 Theory... is a bit eccentric in its presentation and doesn't help the
 reader build intuition.

I have written an overview of various category theory books, which you may find 
useful, at the following site:

Learning Haskell through Category Theory, and Adventuring in Category Land: 
Like Flatterland, Only About Categories
http://dekudekuplex.wordpress.com/2009/01/16/learning-haskell-through-category-theory-and-adventuring-in-category-land-like-flatterland-only-about-categories/

Hope this helps.

-- Benjamin L. Russell
-- 
Benjamin L. Russell  /   DekuDekuplex at Yahoo dot com
http://dekudekuplex.wordpress.com/
Translator/Interpreter / Mobile:  +011 81 80-3603-6725
Furuike ya, kawazu tobikomu mizu no oto. -- Matsuo Basho^ 

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


[Haskell-cafe] Re: sendfile leaking descriptors on Linux?

2010-02-06 Thread Bardur Arantsson

Bardur Arantsson wrote:

(sorry about replying-to-self)

During yet another bout of debugging, I've added even more I am here 
instrumentation code to the SendFile code, and the culprit seems to be

 threadWaitWrite.

I think I've pretty much confirmed this.

I've changed the code again. This time to:

 sendfile :: Fd - Fd - Ptr Int64 - Int64 - IO Int64
 sendfile out_fd in_fd poff bytes = do
 putStrLn PRE-threadWaitWrite
 -- threadWaitWrite out_fd
 -- putStrLn AFTER threadWaitWrite
 sbytes - c_sendfile out_fd in_fd poff (fromIntegral bytes)
 putStrLn $ AFTER c_sendfile; result was:  ++ (show sbytes)
 if sbytes = -1
   then do errno - getErrno
   if errno == eAGAIN
 then do
threadDelay 100
sendfile out_fd in_fd poff bytes
 else throwErrno Network.Socket.SendFile.Linux
  else return (fromIntegral sbytes)

That is, I removed the threadWaitWrite in favor of just adding a
threadDelay 100 when eAGAIN is encountered.

With this code, I cannot provoke the leak.

Unfortunately this isn't really a solution -- the CPU is pegged at
~50% when I do this and it's not exactly elegant to have a hardcoded
100 ms delay in there. :)

I'm hoping that someone who understands the internals of GHC can chime
in here with some kind of explanation as to if/why/how threadWaitWrite can
fail in this way.

Anyone?

Cheers,

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


Re: [Haskell-cafe] Re: Category Theory woes

2010-02-06 Thread briand
On Sun, 07 Feb 2010 01:38:08 +0900
Benjamin L. Russell dekudekup...@yahoo.com wrote:

 On Tue, 02 Feb 2010 09:16:03 -0800, Creighton Hogg wrote:
 
  2010/2/2 Álvaro García Pérez agar...@babel.ls.fi.upm.es
  
  You may try Pierce's Basic Category Theory for Computer
  Scientists or Awodey's Category Theory, whose style is rather
  introductory. Both of them (I think) have a chapter about functors
  where they explain the Hom functor and related topics.
 
  
  I think Awodey's book is pretty fantastic, actually, but I'd avoid
  Pierce. Unlike Types and Programming Languages, I think Basic
  Category Theory... is a bit eccentric in its presentation and
  doesn't help the reader build intuition.
 
 I have written an overview of various category theory books, which
 you may find useful, at the following site:
 
 Learning Haskell through Category Theory, and Adventuring in Category
 Land: Like Flatterland, Only About Categories
 http://dekudekuplex.wordpress.com/2009/01/16/learning-haskell-through-category-theory-and-adventuring-in-category-land-like-flatterland-only-about-categories/
 
 Hope this helps.

It does.

Does anybody have any opinions on Pitt, Category Theory and Computer
Science ?


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


[Haskell-cafe] safe-lazy-io on GHC 6.12?

2010-02-06 Thread Tom Tobin
After convincing myself the hard way that you can't be lazy across
strict monadic results (by writing myself a foldrM -- yeah, I'm
still a beginner), I noticed the recent discussion of safe-lazy-io vs.
iteratee with interest.  The safe-lazy-io package seems much easier to
understand than iteratee, but it doesn't compile on GHC 6.12 (and I
haven't had any luck in figuring out how to update it myself).  The
Hackage build log shows the same build result I'm getting [1]; is
there any chance of it getting updated to work on 6.12?

[1] 
http://hackage.haskell.org/packages/archive/safe-lazy-io/0.1/logs/failure/ghc-6.12
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] safe-lazy-io on GHC 6.12?

2010-02-06 Thread Nicolas Pouillard
On Sat, 6 Feb 2010 11:38:25 -0600, Tom Tobin korp...@korpios.com wrote:
 After convincing myself the hard way that you can't be lazy across
 strict monadic results (by writing myself a foldrM -- yeah, I'm
 still a beginner), I noticed the recent discussion of safe-lazy-io vs.
 iteratee with interest.  The safe-lazy-io package seems much easier to
 understand than iteratee, but it doesn't compile on GHC 6.12 (and I
 haven't had any luck in figuring out how to update it myself).  The
 Hackage build log shows the same build result I'm getting [1]; is
 there any chance of it getting updated to work on 6.12?

Right, updating it is on my todo list.

However I have a little dilemma, safe-lazy-io has a local version of
hGetContents because I needed a version which do not hide exceptions.

However the latest version of hGetContents seems to no longer catch
exceptions (am I right?), if so it might be preferable to just use
the new hGetContents. Or not?

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


Re: [Haskell-cafe] Using ShowS or Difference Lists

2010-02-06 Thread Ryan Ingram
As other people have mentioned, you are duplicating library
functionality.  But nobody has actually talked about the performance
characteristics of your code.

Fortunately for you, the calls to (++) in your recursion are
right-associative, so you don't have an asymptotic problem where your
program gets slower and slower for large inputs; it should stay
linear.

But you are wasting some work.  In particular, (concat (intersperse 
 l)) produces a String, and then (++) duplicates all of the cons
cells in that string as it rebuilds it so that the tail connects with
the next string.

So there is a potential benefit to using a difference list, albeit
only by around a 2x factor.

  -- ryan

On Sat, Feb 6, 2010 at 4:42 AM, Mark Spezzano
mark.spezz...@chariot.net.au wrote:
 Hi,

 Just wondering whether I can use ShowS or tupling or Difference Lists to 
 speed up the following code?

 It's basic text processing. It takes in a list of Lines where each Line is a 
 list of Words and intersperses   between them then concatenates them into a 
 longer String. Note that there is a recursive call and the ++ operator.

 Thanks

 Mark


 -- Function: joinLines
 -- Joins the Words within Lines together with whitespace and newline 
 characters
 -- Argument: Lines to pad with whitespace and newlines
 -- Evaluate: The processed and concatenated String
 joinLines :: [Line] - String
 joinLines (l:[]) = concat (intersperse   l)
 joinLines (l:ls) = (concat (intersperse   l)) ++ ('\n':joinLines ls)

 ___
 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] a beginner question: decorate-op-undecorate

2010-02-06 Thread Aran Donohue
One way or the other, this has been a very productive question for getting
good pointers on what to read about next...

Thanks again.
Aran

On Sat, Feb 6, 2010 at 8:18 AM, Stephen Tetley stephen.tet...@gmail.comwrote:

 Hi John

 I'm not sure about making Binding polymorphic to get Functor,
 Traversable, Foldable...

 While I think you're correct that partitionEithers might not be a
 useful example to draw from in this case, I'd assume that Binding
 would be part of a larger syntax-tree, thus there might not be a
 appropriate single leaf to make the tree polymorphic on. Felipe
 Lessa's point - to use Uniplate or one of the Generics packages -
 might be a better candidate for implementing traversals.

 Best wishes

 Stephen
 ___
 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] Re: sendfile leaking descriptors on Linux?

2010-02-06 Thread Thomas Hartman
me too.

2010/2/5 MightyByte mightyb...@gmail.com:
 I've been seeing a steady stream of similar resource vanished messages
 for as long as I've been running my happstack app.  This message I get
 is this:

 socket: 58: hClose: resource vanished (Broken pipe)

 I run my app from a shell script inside a while true loop, so it
 automatically gets restarted if it crashes.  This incurs no more than
 a few seconds of down time.  Since that is acceptable for my
 application, I've never put much effort into investigating the issue.
 But I don't think the resource vanished error results in program
 termination.  When I have looked into it, I've had similar trouble
 reproducing it.  Clients such as wget and firefox don't seem to cause
 the problem.  If I remember correctly it only happens with IE.

 On Fri, Feb 5, 2010 at 2:56 AM, Bardur Arantsson s...@scientician.net wrote:
 Jeremy Shaw wrote:

 Actually,

 We should start by testing if native sendfile leaks file descriptors even
 when the whole file is sent. We have a test suite, but I am not sure if it
 tests for file handle leaking...


 I should have posted this earlier, but the exact message I'm seeing in the
 case where the Bad Client disconnects is this:

   hums: Network.Socket.SendFile.Linux: resource vanished (Broken pipe)

 Oddly, I haven't been able to reproduce this using a wget client with a ^C
 during transfer. When I disconnect wget with ^C or pkill wget or even
 pkill -9 wget, I get this message:

  hums: Network.Socket.SendFile.Linux: resource vanished (Connection reset by
 peer)

 (and no leak, as observed by lsof | grep hums).

 So there appears to be some vital difference between the handling of the two
 cases.

 Another observation which may be useful:

 Before the sendfile' API change (Handle - FilePath) in sendfile-0.6.x, my
 code used withFile to open the file and to ensure that it was closed. So
 it seems that withBinaryFile *should* also be fine. Unless the Broken pipe
 error somehow escapes the scope without causing a close.

 I don't have time to dig more right now, but I'll try to see if I can find
 out more later.

 Cheers,

 ___
 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 mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] cannot post to haskellmode-em...@projects.haskell.org

2010-02-06 Thread Jose A. Ortega Ruiz

Hi,

all my posts to the haskellmode-emacs list (using the address in the
subject) are being rejected with the error:

  451 451 Temporary local problem - please try later (state 18)

(after several retries by the Google smtp server, which i use as a
smarthost).

Any idea of what could be causing this problem?

Thanks!
jao
-- 
There are two ways to write error-free programs; only the third one
works.
  - Alan Perlis, Epigrams in Programing

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


Re: [Haskell-cafe] cannot post to haskellmode-em...@projects.haskell.org

2010-02-06 Thread Jens Petersen
On 7 February 2010 07:39, Jose A. Ortega Ruiz j...@gnu.org wrote:
 all my posts to the haskellmode-emacs list (using the address in the
 subject) are being rejected with the error:
  451 451 Temporary local problem - please try later (state 18)
 (after several retries by the Google smtp server, which i use as a
 smarthost).

I have been experiencing this often too recently when trying to
post to haskell-platform list.  I wonder if some of the googlemail
smtp servers got blacklisted on projects.haskell.org because of
spam?

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


[Haskell-cafe] ANN: data-ordlist-0.2

2010-02-06 Thread Leon Smith
I have released data-ordlist 0.2,  with a number of changes:

1.  The module name is now Data.List.Ordered,  instead of Data.OrdList

2.  Three bugfixes: (ack!)  insertSet and insertBag assumed reverse-ordered
lists,   nub failed to remove duplicates.   Thanks to Topi Karvonen for
reporting the first problem.

3.  One semantic change:  old_nubBy f == new_nubBy (not . f).   The new
version is better keeping with the spirit of the rest of the library,  and
makes the old nub bug much more obvious.  Now nubBy is the greedy algorithm
that returns a sublist such that for all binary predicates:

   isSortedBy pred (nubBy pred xs) == True

4.  Improved documentation,  I hope!   Please consider taking a look and
letting me know what you think.

http://hackage.haskell.org/package/data-ordlist

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