Re: [Haskell-cafe] Status of TypeDirectedNameResolution proposal?

2009-11-17 Thread Levi Greenspan
On Tue, Nov 17, 2009 at 1:18 PM, Simon Peyton-Jones
simo...@microsoft.com wrote:
 | What's the status of the TDNR proposal [1]? Personally I think it is a
 | very good idea and I'd like to see it in Haskell'/GHC rather sooner
 | than later. Working around the limitations of the current record
 | system is one of my biggest pain points in Haskell and TDNR would be a
 | major improvement. Thus I wonder if someone is actively working on
 | this proposal?

 It's stalled.  As far as I know, there's been very little discussion about 
 it.  It's not a trivial thing to implement, and it treads on delicate 
 territory (how . is treated).  So I'd need to be convinced there was a 
 strong constituency who really wanted it before adding it.

Well, implementing certain protocols (e.g. based on JSON, like Bayeux
[1]) in a type-safe way requires lots of records and many of these
records have similar selectors, e.g. channel. Currently one can only
have a nice interface to such a protocol by using type classes and
creating lots of instance declarations, which is a lot of boilerplate
to be written. This would be much easier with TDNR, than with
module-scoped record selectors. Also the hack to use different modules
is further complicated by the fact that at least GHC insists on having
each module in a separate file.

As pointed out by others one may choose a different string instead of
. like -  if this makes the implementation of TDNR feasible. But
some mechanism to have some sort of scoped record selectors or TDNR is
needed in my opinion.

Many thanks,
Levi


[1] http://svn.cometd.org/trunk/bayeux/bayeux.html


 I've added an informal straw poll to the bottom of [1] to allow you to 
 express an opinion.

 Also I'm not very happy with the stacking operations part, and I'd like a 
 better idea.

 Simon


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


Re: [Haskell-cafe] Status of TypeDirectedNameResolution proposal?

2009-11-17 Thread Levi Greenspan
On Tue, Nov 17, 2009 at 1:18 PM, Simon Peyton-Jones
simo...@microsoft.com wrote:
 I've added an informal straw poll to the bottom of [1] to allow you to 
 express an opinion.

Forgive my ignorance, but I can not find a way to edit the wiki page.
What am I doing wrong?

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


[Haskell-cafe] Status of TypeDirectedNameResolution proposal?

2009-11-16 Thread Levi Greenspan
What's the status of the TDNR proposal [1]? Personally I think it is a
very good idea and I'd like to see it in Haskell'/GHC rather sooner
than later. Working around the limitations of the current record
system is one of my biggest pain points in Haskell and TDNR would be a
major improvement. Thus I wonder if someone is actively working on
this proposal?

Thanks,
Levi.


[1]   
http://hackage.haskell.org/trac/haskell-prime/wiki/TypeDirectedNameResolution
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Monad woes

2009-08-23 Thread Levi Greenspan
Hi all,

I try to create a simple monad using a stack of Reader and IO but when
using it, I encounter some problems. The Monad is defined as M a:

{-# LANGUAGE GeneralizedNewtypeDeriving #-}
module Main where

import Control.Monad.Reader
import Control.Concurrent

newtype M a = M {
unM :: ReaderT String IO a
} deriving (Monad, MonadIO, MonadReader String)

runM :: String - M a - IO a
runM s m = runReaderT (unM m) s

loop :: (String - M ()) - M ()
loop f = forever $ f hello


I then define a callback function to be invoked by 'loop':


callback :: String - M ()
callback s = liftIO $ print s  threadDelay 100


So far so good. Then I test it like this:


test1 :: IO ()
test1 = runM foo $ do
loop callback
liftIO $ print here -- OK. Never reached


Still works fine. 'loop' never returns. In a real life application
'loop' is an event loop and I'd like to fork it into a new thread like
this:


test3 :: IO ()
test3 = runM foo $ liftIO $ do
forkIO $ do
return $ loop callback
return ()
print here
threadDelay 200


This not only looks ugly, it also doesn't work. For 'loop callback' to
pass the type checker, it had to be returned into the IO monad. But I
guess due to laziness, 'loop' will never be called. This can be
confirmed without forkIO:


test2 :: IO ()
test2 = runM foo $ liftIO $ do
return $ loop callback
print here


Again, 'loop callback' will not be invoked.

Now, given that I must find a way to combine IO and my M monad I don't
know what to try next. Prima facie it seems I must somehow force 'loop
callback' to be evaluated, but how? Not to mention all the liftIO
clutter. I would greatly appreciate some help here.

Thank you very much!

Cheers,
Levi
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
module Main where

import Control.Monad.Reader
import Control.Concurrent

newtype M a = M {
unM :: ReaderT String IO a
} deriving (Monad, MonadIO, MonadReader String) 

runM :: String - M a - IO a
runM s m = runReaderT (unM m) s

loop :: (String - M ()) - M ()
loop f = forever $ f hello

callback :: String - M ()
callback s = liftIO $ print s  threadDelay 100

test1 :: IO ()
test1 = runM foo $ do
loop callback
liftIO $ print here

test2 :: IO ()
test2 = runM foo $ liftIO $ do
return $ loop callback
print here

test3 :: IO ()
test3 = runM foo $ liftIO $ do
forkIO $ do
return $ loop callback
return ()
print here
threadDelay 200

main :: IO ()
main = do
print test3
test3
print test2
test2
print test1
test1

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


Re: [Haskell-cafe] Monad woes

2009-08-23 Thread Levi Greenspan
Hi Jeremy,

On Sun, Aug 23, 2009 at 5:08 PM, Jeremy Shawjer...@n-heptane.com wrote:
 What you probably want is:

 test2' :: IO ()
 test2' = runM foo $ do
    loop callback
    liftIO $ print here

This equals my test1 version which is fine without forkIO.

 return $ loop callback :: (Monad m) = IO (M ())

 It is an IO operation which returns a value of type, M (). But,
 nothing is done with that value, it is just thrown away.

I see. This is what I feared.

 If you want to add a forkIO, the forkIO must go before the runM:

OK. I tried all kinds of combinations, but not forkIO in front of
'runM' . The reason being that I only use forkIO because 'loop' never
returns so in order to proceed I would have to put it into the
background. Basically I want two threads running inside the same M
monad.

 hope this helps.

Many thanks Jeremy. Your explanations are indeed very helpful. But
they also strengthen my gut feeling that running two threads in the
same M monad is hard (if not impossible) to do.

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


Re: [Haskell-cafe] Monad woes

2009-08-23 Thread Levi Greenspan
On Sun, Aug 23, 2009 at 5:21 PM, Jeremy Shawjer...@n-heptane.com wrote:
 Also, you could define a forkM function like this:

 forkM :: M () - M ThreadId
 forkM (M r) = M $ mapReaderT forkIO r

 which could be used like this:

 test = runM foo $ do
         forkM $ loop callback
         liftIO $ print here

 If we were to expand forkM in test, we would get something like:

 test' = runM foo $ do
          env - ask
          liftIO $ forkIO (runM env $ loop callback)
          liftIO $ print here

 So, this does not change the 'rule' of forkIO having to come before a
 runM. It just wraps it up nicely.

Somehow I missed this e-mail when I replied last time. Now this is
actually the solution to my problem. I didn't think of a second runM
with the same environment. Brilliant (OTOH it probably highlights the
fact that I am only a Monad novice).

Many thanks Jeremy. You saved my day!

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


[Haskell-cafe] Re: FFI: Problem with Signal Handler Interruptions

2009-08-07 Thread Levi Greenspan
On Thu, Aug 6, 2009 at 12:17 PM, Simon Marlowmarlo...@gmail.com wrote:
 The SIGVTALRM signal is delivered to one (random) thread in the program, so
 I imagine it just isn't being delivered to the thread that runs your second
 call to sleep.  (the main Haskell thread is a bound thread and hence gets
 an OS thread to itself).

In addition to my last e-mail - would you say that blocking SIGVTALRM
in the thread that runs sleep (or poll etc.) is the right thing to do
in order to avoid the problem of getting EINTR? E.g. for the main
thread:

{-# LANGUAGE ForeignFunctionInterface #-}
module Main where

import Foreign.C.Types
import Control.Concurrent
import System.Posix.Signals
import Control.Monad

blockSIGVTALRM :: IO ()
blockSIGVTALRM = addSignal virtualTimerExpired `liftM` getSignalMask =
blockSignals  return ()

sleep :: IO ()
sleep = blockSIGVTALRM  c_sleep 3 = print

main :: IO ()
main = sleep

foreign import ccall safe unistd.h sleep
c_sleep :: CUInt - IO CUInt


How much would the thread scheduling be affected by this?

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


[Haskell-cafe] Re: FFI: Problem with Signal Handler Interruptions

2009-08-06 Thread Levi Greenspan
Hi Simon,

Many thanks for your reply. I am not actually using sleep in my code.
I only used it for here for highlighting the problem. It will be the
same when using poll(2) for instance. Does this mean that because of
SIGVTALRM I can always get an EINTR when calling a foreign function
that blocks on a system call?

Cheers,
Levi

On Thu, Aug 6, 2009 at 12:17 PM, Simon Marlowmarlo...@gmail.com wrote:
 The SIGVTALRM signal is delivered to one (random) thread in the program, so
 I imagine it just isn't being delivered to the thread that runs your second
 call to sleep.  (the main Haskell thread is a bound thread and hence gets
 an OS thread to itself).

 Is there some reason you can't use threadDelay?  threadDelay is much more
 friendly: it doesn't require another OS thread for each sleeping Haskell
 thread.

 Cheers,
        Simon

 On 05/08/2009 17:01, Levi Greenspan wrote:

 Nobody?

 On Tue, Aug 4, 2009 at 10:06 AM, Levi
 Greenspangreenspan.l...@googlemail.com  wrote:

 Dear list members,

 In February this year there was a posting Why does sleep not work?

 (http://www.haskell.org/pipermail/haskell-cafe/2009-February/055400.html).
 The problem was apparently caused by signal handler interruptions. I
 noticed the same (not with sleep though) when doing some FFI work and
 compiled the following test program:


 {-# LANGUAGE ForeignFunctionInterface #-}
 module Main where

 import Foreign.C.Types
 import Control.Concurrent

 sleep :: IO ()
 sleep = c_sleep 3= print

 fails :: IO ()
 fails = sleep

 works :: IO ()
 works = forkIO sleep  return ()

 main :: IO ()
 main = fails  works  threadDelay 300

 foreign import ccall unsafe unistd.h sleep
    c_sleep :: CUInt -  IO CUInt


 When compiled with GHC (using --make -threaded), it will print 3
 immediately (from the fails function) and after 3 seconds 0 (from
 works), before it finally exits. man sleep(3) tells me that sleep
 returns 0 on success and if interrupted by a signal the number of
 seconds left to sleep. Clearly fails is interrupted by a signal
 (which seems to be SIGVTALRM). This was mentioned in the discussion
 from February.

 I would like to know why fails fails and works works, i.e. why is
 sleep not interrupted when run in a separate thread? And what can be
 done to make sleep work in the main thread? It wouldn't be wise to
 block SIGVTALRM, wouldn't it?

 Many thanks,
 Levi



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


[Haskell-cafe] Re: FFI: Problem with Signal Handler Interruptions

2009-08-05 Thread Levi Greenspan
Nobody?

On Tue, Aug 4, 2009 at 10:06 AM, Levi
Greenspangreenspan.l...@googlemail.com wrote:
 Dear list members,

 In February this year there was a posting Why does sleep not work?
 (http://www.haskell.org/pipermail/haskell-cafe/2009-February/055400.html).
 The problem was apparently caused by signal handler interruptions. I
 noticed the same (not with sleep though) when doing some FFI work and
 compiled the following test program:


 {-# LANGUAGE ForeignFunctionInterface #-}
 module Main where

 import Foreign.C.Types
 import Control.Concurrent

 sleep :: IO ()
 sleep = c_sleep 3 = print

 fails :: IO ()
 fails = sleep

 works :: IO ()
 works = forkIO sleep  return ()

 main :: IO ()
 main = fails  works  threadDelay 300

 foreign import ccall unsafe unistd.h sleep
    c_sleep :: CUInt - IO CUInt


 When compiled with GHC (using --make -threaded), it will print 3
 immediately (from the fails function) and after 3 seconds 0 (from
 works), before it finally exits. man sleep(3) tells me that sleep
 returns 0 on success and if interrupted by a signal the number of
 seconds left to sleep. Clearly fails is interrupted by a signal
 (which seems to be SIGVTALRM). This was mentioned in the discussion
 from February.

 I would like to know why fails fails and works works, i.e. why is
 sleep not interrupted when run in a separate thread? And what can be
 done to make sleep work in the main thread? It wouldn't be wise to
 block SIGVTALRM, wouldn't it?

 Many thanks,
 Levi

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


[Haskell-cafe] FFI: Problem with Signal Handler Interruptions

2009-08-04 Thread Levi Greenspan
Dear list members,

In February this year there was a posting Why does sleep not work?
(http://www.haskell.org/pipermail/haskell-cafe/2009-February/055400.html).
The problem was apparently caused by signal handler interruptions. I
noticed the same (not with sleep though) when doing some FFI work and
compiled the following test program:


{-# LANGUAGE ForeignFunctionInterface #-}
module Main where

import Foreign.C.Types
import Control.Concurrent

sleep :: IO ()
sleep = c_sleep 3 = print

fails :: IO ()
fails = sleep

works :: IO ()
works = forkIO sleep  return ()

main :: IO ()
main = fails  works  threadDelay 300

foreign import ccall unsafe unistd.h sleep
c_sleep :: CUInt - IO CUInt


When compiled with GHC (using --make -threaded), it will print 3
immediately (from the fails function) and after 3 seconds 0 (from
works), before it finally exits. man sleep(3) tells me that sleep
returns 0 on success and if interrupted by a signal the number of
seconds left to sleep. Clearly fails is interrupted by a signal
(which seems to be SIGVTALRM). This was mentioned in the discussion
from February.

I would like to know why fails fails and works works, i.e. why is
sleep not interrupted when run in a separate thread? And what can be
done to make sleep work in the main thread? It wouldn't be wise to
block SIGVTALRM, wouldn't it?

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


Re: [Haskell-cafe] Slow Text.JSON parser

2009-01-18 Thread Levi Greenspan
On Sun, Jan 18, 2009 at 6:07 AM, Sigbjorn Finne
sigbjorn.fi...@gmail.com wrote:

 Maybe. Handling the common cases reasonably well is
 probably worth doing first (+profiling) before opting for
 a heartlung transplant..

 To wit, I've trivially improved the handling of string and
 integer lits in version 0.4.3 (just released.) It cuts down
 the running times by a factor of 2-3 on larger inputs --

Indeed, I have just tried version 0.4.3 and my previous test which
took about 3 seconds to run is now running in about one second. Very
nice improvement. Thanks for all your work Sigbjorn.

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


Re: [Haskell-cafe] ANN: HTTPbis / HTTP-4000.x package available

2009-01-16 Thread Levi Greenspan
Sounds very good to me. However I would like to as one question
regarding the HTTP lib. On hackage I read: HTTP: A library for
client-side HTTP. Maybe you or someone on this list can tell me what
the restrictions of the HTTP library are that restrict it to client
side. What would be required to enable it for server-side use as well?
Is it planed to complete HTTP this way?

Many thanks,
Levi

On Fri, Jan 16, 2009 at 7:36 AM, Sigbjorn Finne
sigbjorn.fi...@gmail.com wrote:
 Hi,

 I guess it's time to publish more widely the availability of a modernization
 of
 the venerable and trusted HTTP package, which I've been working on
 offon for a while.

 Bunch of changes, but the headline new feature of this new version
 is the parameterization of the representation of payloads in both HTTP
 requests and responses. Two new representations are supported, strict and
 lazy
 ByteStrings. Some people have reported quietly pleasing speedups as a result
 of this change. (If they want to report numbers, please do..)

 Another change/fix in this release is the _alleged_ fix to the long-standing
 bug
 in the use of  absolute URIs vs absolute paths in requests (for non-proxied
 and
 proxied use.) Give it a go..

 Notice that the HTTP-4000.x version will require you to make some
 modifications to your existing HTTP-using code -- I've tried to keep the API
 backwards compatible minimal despite the change in functionality and
 underlying types. If you do not want to deal with this right away, please
 introduce a 4000 dependency on the HTTP package in your .cabal files.

 I've also taken on the maintainership of the package, with the highly
 esteemed
 Bjorn Bingert no longer having the usual abundance of cycles to look after
 it (hope I'm not misrepresenting facts here, Bjorn!) However, I've yet to
 gain access to  www.haskell.org and update http://www.haskell.org/http,
 so for now you may pick up a new version the lib via

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

 GIT repo for HTTP-4000  / HTTPbis is here

   git://code.galois.com/HTTPbis.git

 enjoy
 --sigbjorn

 ___
 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] ANN: HTTPbis / HTTP-4000.x package available

2009-01-16 Thread Levi Greenspan
On Fri, Jan 16, 2009 at 8:11 PM, Sigbjorn Finne
sigbjorn.fi...@gmail.com wrote:
 I'm guessing that you are reading something different into that
 than what's intended - it's client-side in the sense that it can
 only issue web requests and handle their responses. i.e., it
 doesn't handle incoming HTTP requests and issue suitable
 responses. Web server implementation is an interesting problem
 in its own right, and many packages/frameworks do an
 admirable job of that already, so no plans (by me) to tackle
 that via the HTTP package.

 But, utilizing the HTTP package as part of any web app you
 expose on a web server is very much on and not out of bounds.
 Go for it! :-)

 Does that answer your Q? (my apologies if I'm stating the
 obvious above.)

Thanks for your reply Sigbjorn. Correct me if I am wrong, but it seems
to me that by using sockets for incoming connections and receiveHTTP
:: Stream s = s - IO (Result Request_String) and respondHTTP ::
Stream s = s - Response_String - IO () from Network.HTTP.Stream
that I could easily handle incoming requests and send responses back.
OK, I need to build up the response myself, but that would be no real
limitation for me.

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


[Haskell-cafe] How to simplify this code?

2009-01-15 Thread Levi Greenspan
Dear list members,

I started looking into monadic programming in Haskell and I have some
difficulties to come up with code that is concise, easy to read and
easy on the eyes. In particular I would like to have a function add
with following type signature: JSON a = MyData - String - a -
MyData. MyData holds a JSValue and add should add a key and a value to
this JSON object. here is what I came up with and I am far from
satisfied. Maybe someone can help me to simplify this...

module Test where

import Text.JSON
import Data.Maybe (isJust, fromJust)
import Control.Monad

data MyData = MyData { json :: JSValue } deriving (Read, Show)

jsObj :: JSValue - Maybe (JSObject JSValue)
jsObj (JSObject o) = Just o
jsObj _ = Nothing

add :: JSON a = MyData - String - a - MyData
add m k v = fromJust $ (return $ json m) = jsObj = (return .
fromJSObject) = (return . ((k, showJSON v):)) = (return .
toJSObject) = (return . showJSON) = \js - (return $ m { json = js
})

add2 :: JSON a = MyData - String - a - MyData
add2 m k v = fromJust $ (\js - m { json = js }) `liftM` (showJSON
`liftM` (toJSObject `liftM` (((k, showJSON v):) `liftM` (fromJSObject
`liftM` (jsObj $ json m)

add3 :: JSON a = MyData - String - a - MyData
add3 = undefined -- How to simplify add?


What the code essentially does is that using functions from Text.JSON,
it gets the list of key-value pairs and conses another pair to it
before wrapping it again in the JSValue-Type.

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


Re: [Haskell-cafe] How to simplify this code?

2009-01-15 Thread Levi Greenspan
On Fri, Jan 16, 2009 at 12:52 AM, Ryan Ingram ryani.s...@gmail.com wrote:
 Here's a series of refactorings that I feel gets to the essence of the code.

Indeed it does.

 Final result:
 modifyJSON f m = m { json = f (json m) }

 add m k v = modifyJSON go m where
 go = showJSON . toJSObject . (newEntry :) . fromJSObject . fromJust . 
 jsObj
 newEntry = (k, showJSON v)

 Some stylistic choices are debatable (pointless vs. not, inline vs.
 not), but I think this is a lot more readable than the = and liftM
 madness you had going.

Definitely. The refactorings you have done are very instructive and
the final result just beautiful. Many many thanks. Exactly the kind of
response I was hoping for.

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


[Haskell-cafe] Slow Text.JSON parser

2009-01-13 Thread Levi Greenspan
Dear list members,

I tried Text.JSON from hackage and did an initial test to see how well
it performs. I created a single JSON file of roughly 6 MB containing a
single JSON array with 30906 JSON objects and used the following code
to parse it:


module Main where

import System.IO
import Data.Time.Clock
import System.Environment
import Text.Printf
import Text.JSON

parse s = do
start - getCurrentTime
let !len = decode s
end - getCurrentTime
print len
printf Elapsed time = %s\n (show $ diffUTCTime end start)
where
decode s = case decodeStrict s of
Ok (JSArray a) - length a
_ - -1

main = do
file - getArgs = return . head
withFile file ReadMode (\h - hGetContents h = parse)



The outcome was something like:

30906
Elapsed time = 2.902755s

on my 2GHz core 2 duo.

Another Java-based JSON parser (Jackson:
http://www.cowtowncoder.com/hatchery/jackson/index.html) gives me:

30906
Elapsed time = 480 ms

Now I wonder why Text.JSON is so slow in comparison and what can be
done about it. Any ideas? Or is the test case invalid?

Thanks,
Levi

---
The Java code for the Jackson test is:

import org.codehaus.jackson.JsonParser;
import org.codehaus.jackson.JsonFactory;
import org.codehaus.jackson.map.JsonTypeMapper;
import org.codehaus.jackson.map.JsonNode;

import java.io.File;

class Test {

public static void main(String[] args) throws Exception {
final long start = System.currentTimeMillis();
final JsonTypeMapper mapper = new JsonTypeMapper();
final JsonParser parser = new
JsonFactory().createJsonParser(new File(args[0]));
final JsonNode root = mapper.read(parser);
final long end = System.currentTimeMillis();
System.out.println(root.size());
System.out.println(String.format(Elapsed time = %d ms, end - start));
}
}
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Will GHC finally support epoll in 2009?

2008-12-31 Thread Levi Greenspan
Ticket #635 Replace use of select() in the I/O manager with
epoll/kqueue/etc. (http://hackage.haskell.org/trac/ghc/ticket/635)
dates back from 2005. Now its 2009 and GHC can handle hundreds of
thousands of threads, yet having more than 1024 file descriptors open
is still impossible. This limitation is a real bottle neck and
prevents some cool developments on server side, like scalable comet
servers. Instead others (e.g. Erlang guys) post stories about how they
achived 1 million comet users (cf.
http://www.metabrew.com/article/a-million-user-comet-application-with-mochiweb-part-1/
).

Hence my question - is it likely that GHC will support epoll in 2009?

Cheers and happy new year!

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


Re: [Haskell-cafe] Libevent FFI problems

2008-07-26 Thread Levi Greenspan
On Fri, 2008-07-25 at 13:45 -0700, Adam Langley wrote:
 I'd suggest that you write your server on the select() based system
 as-is for now. Then, when you need epoll you'll be sufficiently
 motivated to hack up the RTS to include it ;)

The problem with a select() based approach is that I can not have more
than 1024 parallel connections on my Linux system, since this is the
upper limit for the number of file descriptors in the FD_SET used by
select().

Eg.

# ulimit -n 1
# start client with many open connections

client: internal error: awaitEvent: descriptor out of range
(GHC version 6.8.3 for i386_unknown_linux)
Please report this as a GHC bug:
http://www.haskell.org/ghc/reportabug
Aborted

This is caused by having more file descriptors than FD_SETSIZE (which is
1024) on my system. So clearly select() doesn't scale to the numbers I
need :-(

Thanks,
Levi


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


Re: [Haskell-cafe] Libevent FFI problems

2008-07-25 Thread Levi Greenspan
Thanks Adam. It took me some time to realize what you recognized
immediately - xptr is useless. Instead I now bind the additional value
which might be provided on event creation in a closure since the C
code never has to deal with it.

And yes, there are many functions missing. For now I just need the
event notification to detect file descritor (or socket) changes.

Regarding your remark, that the RTS multiplexes IO already I am usure
how this works out in practice. The reason I write this wrapper is
that I want a network server which can handle thousands of
connections. And to not require a permanent thread for each I would
like to use something like select in C or Selector in Java. I haven't
found something like this in Haskell, hence the libevent wrapper. If
you have any information how to write something like this without this
wrapper I would be more than happy.

Finally the code still leaks FunPtrs as so far I never free them and
honestly I don't know when to do this. Any ideas?

For reference I have attached a newer version of the wrapper code
(removed the TimeVal stuff since I don't need it).

Thanks again,
Levi

On Fri, Jul 25, 2008 at 7:21 PM, Adam Langley [EMAIL PROTECTED] wrote:
 2008/7/23 Levi Greenspan [EMAIL PROTECTED]:
 I would be grateful for any advices, hints or comments. And I really
 look forward to the FFI section in the Real World Haskell book.

 Generally it looks pretty good. I think I'm missing some C code
 (function wrapper). However, libevent is an odd choice to wrap. The
 RTS already multiplexes IO for Haskell programs. In order not to block
 the RTS, the libevent using code would have to be in its own kernel
 thread.

 Really, the RTS needs to be ported to libevent rather than an FFI wrapping.

 For your specific problem, I see you're allocating xptr, but I don't
 see that you're ever poking a value into it. Indeed, I can't see that
 createEvent ever uses 'x'.

 Hope that helps.




 AGL

 --
 Adam Langley [EMAIL PROTECTED] http://www.imperialviolet.org



hsevent.hsc
Description: Binary data
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Libevent FFI problems

2008-07-25 Thread Levi Greenspan
Thank you (and Christopher) for the link. I have one question though -
I read this ticket in the GHC trac:
http://hackage.haskell.org/trac/ghc/ticket/635 which plans to use
epoll instead of select. The reason I thought of libevent is exactly
the support for epoll and other better-than-select mechanisms. Is
there progress in GHC with regard to this? This is very important for
me since I awill not write a web-server, but rather want to play with
Comet (i.e. having thousands of open connections as it is common for
long-polling in addition to many relatively short request/response
based connections).

However it seems no quite attractive to go with what is offered by GHC
currently instead of writing the libevent wrapper. Just for the sake
of completeness - any insights into the freeFunPtr issue I wrote
about? ;-)

Many thanks to all of you.

- Levi


On Fri, Jul 25, 2008 at 10:05 PM, Adam Langley [EMAIL PROTECTED] wrote:
 2008/7/25 Krzysztof Skrzętnicki [EMAIL PROTECTED]:
 Developing a high-performance web server in Concurrent Haskell
 http://www.haskell.org/~simonmar/papers/web-server-jfp.pdf (see page 15)

 Perhaps you might be interested in this paper also because of its topic.

 That's a good reference. Also note that the paper is 6 years old and
 GHC has come a long way since then. I'd suspect that the graph on page
 15 would look much more favourable to Haskell these days.


 AGL

 --
 Adam Langley [EMAIL PROTECTED] http://www.imperialviolet.org

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


[Haskell-cafe] Libevent FFI problems

2008-07-23 Thread Levi Greenspan
Dear list members,

This is my first attempt to create a FFI to libevent
(http://monkey.org/~provos/libevent/) which is an event notification
library. A simple usage example is for instance given here:
http://unx.ca/log/libevent_echosrv1c/ . In C one basically creates
struct event instances which are initialized with a callback function
and the kind of event (e.g. read) one is intested in. Optionally a
data argument can be given which will be passed to the callback
function when invoked eventually. An event dispatcher loop will invoke
the callback when the event occurs.

I have attached my first attempt at a FFI to libevent. However it
doesn't work correctly. In the client code I want to pass 99 as data
to the callback function, but what is printed out is 0. I guess there
is an issue with pointer derefencing, but I don't know.

Also I am not sure how to handle the FunPtr deallocation. Since the
FunPtr is stored in the foreign event structure I don't know when I
can free it.

I would be grateful for any advices, hints or comments. And I really
look forward to the FFI section in the Real World Haskell book.

Thank you very much.

- Levi


hsevent.hsc
Description: Binary data
module Main where

import System.IO
import Network.Socket
import Network.Stream
import Network.HTTP
import Network.URI
import Control.Monad
import Control.Exception
import Control.Concurrent
import System.Posix.IO
import System.Posix.Types

import Event as E
import qualified Data.Map as Map

callback :: Fd - E.EventType - Int - IO ()
callback fd e x = do
print fd
print e
print x

main :: IO ()
main = 
withSocketsDo $ do
E.init
addrinfos - getAddrInfo (Just (defaultHints {addrFlags = [AI_PASSIVE]}))
 Nothing 
 (Just 1234)

let serveraddr = head addrinfos

-- create server socket
sock - socket (addrFamily serveraddr) Stream defaultProtocol

-- bind it to the address we're listening to
bindSocket sock (addrAddress serveraddr)

-- start listening for connection requests
-- max. connection requests waiting to be accepted = 5 (max. queue size)
listen sock 5

ev - E.createEvent (Fd (fdSocket sock)) [E.ReadEvent, E.WriteEvent] callback 99
E.addEvent ev Nothing
E.dispatch
return ()

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