[Haskell-cafe] First go at reactive programming

2008-01-15 Thread Levi Stephen

Hi,

Listed below is my first experiment with reactive programming. It is a 
simple web server written using the Data.Reactive[1] library. The 
intended interface is given by the runHttpServer function, so the 
remainder is intended to be internal.


I'd be happy to hear comments on any parts of this, but am particularly 
interested in the following:


1. Is this kind of code what is intended from reactive programming?
2a. I'm not sure about passing the (Handle,...) tuple around. Is there a 
way to avoid this?

2b. I'm not sure of the best place to handle possible socket exceptions
2c. I'd like to be able to pass a function of type Event Request -> 
Event Response to runHttpServer, so that reactive programming could be 
used throughout client code also, but the (Handle,...) tuples seem to be 
getting in the way.

3. I have a feeling there's a clearer way to write responseSend.

Thanks,
Levi

[1] http://www.haskell.org/haskellwiki/Reactive

module Main where

import Control.Applicative
import Control.Arrow ((&&&),(>>>))
import Control.Concurrent
import Control.Monad

import Data.Reactive

import Network.BSD
import Network.HTTP
import Network

import System.IO

import Text.XHtml.Strict

type RequestHandler = Request -> Response

main = runHttpServer helloWorldHandler

helloWorldHandler :: RequestHandler
helloWorldHandler _ =  Response (2,0,0) "" [] $ prettyHtml helloWorldDoc

helloWorldDoc = header << thetitle << "Hello World"
   +++ body << h1 << "Hello World"

runHttpServer r = socketServer >>= runE . handleConnection r

socketServer :: IO (Event Handle)
socketServer = withSocketsDo $ do
 (e,snk) <- mkEventShow "Server"
 sock <- listenOn (PortNumber 8080)
 forkIO $ forever $ acceptConnection sock $ snk
 return e

handleConnection :: RequestHandler -> Event Handle -> Event (IO ())
handleConnection r = handleToRequest >>> runRequestHandler r >>> 
responseSend



handleToRequest :: Event Handle -> Event (Handle, IO (Result Request))
handleToRequest e = fmap (id &&& receiveHTTP) e

responseSend :: Event (Handle, IO (Result Response)) -> Event (IO ())
responseSend e = fmap (\(h,rsp) -> rsp >>= either (putStrLn . show) 
(respondHTTP h) >> close h) e


runRequestHandler :: RequestHandler -> Event (Handle, IO (Result 
Request)) -> Event (Handle, IO (Result Response))

runRequestHandler r e = fmap hrToHr e
 where
   rqhdl :: Result Request -> Result Response
   rqhdl rq =  bindE rq (Right . r)
   hrToHr :: (Handle, IO (Result Request)) -> (Handle, IO (Result 
Response))

   hrToHr (h,req) = (h, liftA rqhdl req)

acceptConnection s k = accept s >>= \(h,_,_) -> forkIO $ k h

instance Stream Handle where
 readLine h = hGetLine h >>= \l -> return $ Right $ l ++ "\n"
 readBlock h n = replicateM n (hGetChar h) >>= return . Right
 writeBlock h s = mapM_ (hPutChar h) s >>= return . Right
 close = hClose






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


Re: [Haskell-cafe] First go at reactive programming

2008-01-15 Thread Conal Elliott
Hi Levi,

Delightful!  I'd been hoping for a networking-related use of Reactive.  I
made a few tweaks to clean up the code:

* Factored the fmap out of handleConnection, handleToRequest,
runRequestHandler r, and responseSend, to simplify their
interfaces/semantics (no more events).
* Used (second.fmap) in runRequestHandler in place of explicit
manipulation.  Then factored it out into handleConnection, to simplify
interface/semantics (no more pair/IO).
* Added a few type signatures.
* Replaced (putStrLn . show) with print in responseSend.

Let's play some more with improving on the handle-passing.  Meanwhile, new
version below.  I bet we can make it more functional/elegant, isolating the
IO from a simple & pure core.  For instance, the pattern of accepting
connections and then dialoging on each one smells very like what I have in
mind for the (functional) Event monad.

Cheers,  - Conal

module Main where

import Control.Applicative
import Control.Arrow (second,(&&&),(>>>))
import Control.Concurrent
import Control.Monad

import Data.Reactive

import Network.BSD
import Network.HTTP
import Network

import System.IO

import Text.XHtml.Strict

type RequestHandler = Request -> Response

main = runHttpServer helloWorldHandler

helloWorldHandler :: RequestHandler
helloWorldHandler _ =  Response (2,0,0) "" [] $ prettyHtml helloWorldDoc

helloWorldDoc = header << thetitle << "Hello World"
+++ body   << h1   << "Hello World"

runHttpServer :: RequestHandler -> IO a
runHttpServer r = socketServer >>= runE . fmap (handleConnection r)

socketServer :: IO (Event Handle)
socketServer = withSocketsDo $ do
  (e,snk) <- mkEventShow "Server"
  sock<- listenOn (PortNumber 8080)
  forkIO $ forever $ acceptConnection sock $ snk
  return e

handleConnection :: RequestHandler -> Handle -> IO ()
handleConnection r =
  handleToRequest >>> (second.fmap) (runRequestHandler r) >>> responseSend


handleToRequest :: Handle -> (Handle, IO (Result Request))
handleToRequest = id &&& receiveHTTP

runRequestHandler :: RequestHandler -> Result Request -> Result Response
runRequestHandler r rq =  rq `bindE` (Right . r)

responseSend :: (Handle, IO (Result Response)) -> IO ()
responseSend (h,rsp) =
  rsp >>= either print (respondHTTP h) >> close h

acceptConnection :: Socket -> (Handle -> IO ()) -> IO ThreadId
acceptConnection s k = accept s >>= \(h,_,_) -> forkIO $ k h

instance Stream Handle where
 readLine   h   = hGetLine h >>= \l -> return $ Right $ l ++ "\n"
 readBlock  h n = replicateM n (hGetChar h) >>= return . Right
 writeBlock h s = mapM_ (hPutChar h) s >>= return . Right
 close  = hClose




On Jan 15, 2008 3:29 AM, Levi Stephen <[EMAIL PROTECTED]> wrote:

> Hi,
>
> Listed below is my first experiment with reactive programming. It is a
> simple web server written using the Data.Reactive[1] library. The
> intended interface is given by the runHttpServer function, so the
> remainder is intended to be internal.
>
> I'd be happy to hear comments on any parts of this, but am particularly
> interested in the following:
>
> 1. Is this kind of code what is intended from reactive programming?
> 2a. I'm not sure about passing the (Handle,...) tuple around. Is there a
> way to avoid this?
> 2b. I'm not sure of the best place to handle possible socket exceptions
> 2c. I'd like to be able to pass a function of type Event Request ->
> Event Response to runHttpServer, so that reactive programming could be
> used throughout client code also, but the (Handle,...) tuples seem to be
> getting in the way.
> 3. I have a feeling there's a clearer way to write responseSend.
>
> Thanks,
> Levi
>
> [1] http://www.haskell.org/haskellwiki/Reactive
>
> module Main where
>
> import Control.Applicative
> import Control.Arrow ((&&&),(>>>))
> import Control.Concurrent
> import Control.Monad
>
> import Data.Reactive
>
> import Network.BSD
> import Network.HTTP
> import Network
>
> import System.IO
>
> import Text.XHtml.Strict
>
> type RequestHandler = Request -> Response
>
> main = runHttpServer helloWorldHandler
>
> helloWorldHandler :: RequestHandler
> helloWorldHandler _ =  Response (2,0,0) "" [] $ prettyHtml helloWorldDoc
>
> helloWorldDoc = header << thetitle << "Hello World"
>+++ body << h1 << "Hello World"
>
> runHttpServer r = socketServer >>= runE . handleConnection r
>
> socketServer :: IO (Event Handle)
> socketServer = withSocketsDo $ do
>  (e,snk) <- mkEventShow "Server"
>  sock <- listenOn (PortNumber 8080)
>  forkIO $ forever $ acceptConnection sock $ snk
>  return e
>
> handleConnection :: RequestHandler -> Event Handle -> Event (IO ())
> handleConnection r = handleToRequest >>> runRequestHandler r >>>
> responseSend
>
>
> handleToRequest :: Event Handle -> Event (Handle, IO (Result Request))
> handleToRequest e = fmap (id &&& receiveHTTP) e
>
> responseSend :: Event (Handle, IO (Result Response)) -> Event (IO ())
> responseSend e = fmap (\(h,rsp) -> rsp >>= either (putStrLn . show)
> (respondHTTP h) >> close h)

Re: [Haskell-cafe] First go at reactive programming

2008-01-17 Thread Levi Stephen

Hi,

Below is a version that was aimed at getting rid of the (Handle,IO 
(Request a)) tuples and as a result made it easier to remove the IO 
monad from some types, but I don't think it removed it completely from 
any methods.


module Main where

import Control.Applicative
import Control.Concurrent
import Control.Monad

import Data.Reactive

import Network.BSD
import Network.HTTP
import Network

import System.IO

import Text.XHtml.Strict

type RequestHandler = Request -> Response

main = runHttpServer helloWorldHandler

helloWorldHandler :: RequestHandler
helloWorldHandler =  Response (2,0,0) "" [] . prettyHtml . helloWorldDoc

helloWorldDoc :: Request -> Html
helloWorldDoc rq = header << thetitle << "Hello World"
  +++ body   << (h1 << "Hello World" +++ p << show rq)

runHttpServer :: RequestHandler -> IO a
runHttpServer r = socketServer >>= runE . fmap (handleConnection r)

socketServer :: IO (Event Handle)
socketServer = withSocketsDo $ do
 (e,snk) <- mkEventShow "Server"
 sock<- listenOn (PortNumber 8080)
 forkIO $ forever $ acceptConnection sock $ snk
 return e

handleConnection :: Handle -> RequestHandler -> IO ()
handleConnection h r =
 handleToRequest h >>= responseSend h . runRequestHandler r

handleToRequest :: Handle -> IO (Result Request)
handleToRequest = receiveHTTP

runRequestHandler :: RequestHandler -> Result Request -> Result Response
runRequestHandler r rq = rq `bindE` (Right . r)

responseSend :: Handle -> Result Response -> IO ()
responseSend h rsp = either print (respondHTTP h) rsp >> close h

acceptConnection :: Socket -> (Handle -> IO ()) -> IO ThreadId
acceptConnection s k = accept s >>= \(h,_,_) -> forkIO $ k h

instance Stream Handle where
 readLine   h   = hGetLine h >>= \l -> return $ Right $ l ++ "\n"
 readBlock  h n = replicateM n (hGetChar h) >>= return . Right
 writeBlock h s = mapM_ (hPutChar h) s >>= return . Right
 close  = hClose


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


Re: [Haskell-cafe] First go at reactive programming

2008-01-18 Thread Steve Lihn
Tried to install reactive-0.2 on GHC-6.6, but failed.

Building reactive-0.2...
src/Data/Reactive.hs:1:13: cannot parse LANGUAGE pragma

Is the package for GHC 6.8? Is there an older version (0.0?) for GHC
6.6 that I can play with your example? (Or advise how to hack that
file to get it work on 6.6)

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


Re: [Haskell-cafe] First go at reactive programming

2008-01-18 Thread Conal Elliott
Hi Steve,

Thanks for letting me know about the LANGUAGE problem.  Yes, I used
6.8-friendly (6.6-unfriendly) LANGUAGE pragmas.  In retrospect, probably not
such a great idea, since there seem to be many folks still on 6.6.

I just changed the sources (commenting out the LANGUAGE pragmas and
inserting -fglasgow-exts pragmas), darcs-pushed, and put a new version (0.3)
on hackage.  Please give it another try.

Cheers, - Conal

On Jan 18, 2008 7:58 PM, Steve Lihn <[EMAIL PROTECTED]> wrote:

> Tried to install reactive-0.2 on GHC-6.6, but failed.
>
> Building reactive-0.2...
> src/Data/Reactive.hs:1:13: cannot parse LANGUAGE pragma
>
> Is the package for GHC 6.8? Is there an older version (0.0?) for GHC
> 6.6 that I can play with your example? (Or advise how to hack that
> file to get it work on 6.6)
>
> Thanks,
> Steve
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] First go at reactive programming

2008-01-19 Thread Steve Lihn
Reactive-0.3 seems to have a dependency on TypeCompose-0.3. Earlier
version does not work (for lack of Data.Pair). This probably should be
specified in Cabal file.

I aslo fixed all the LANGUAGE problems and now encountered the
following error in TypeCompose:

[4 of 9] Compiling Control.Compose  ( src/Control/Compose.hs,
dist/build/Control/Compose.o )
src/Control/Compose.hs:561:0: parse error on input `deriving'

I tried to restored the commented out "deriving Monoid" and got pass
that. Not sure if that is right though. Back to reactive-0.3, I
encountered:

src/Data/Future.hs:60:27:
Module `Control.Monad' does not export `forever'

Forever is in the latest library, but not in my GHC 6.6. I am not sure
how to get this fixed. Any suggestion?

http://www.haskell.org/ghc/docs/latest/html/libraries/base/Control-Monad.html


Steve


On Jan 19, 2008 1:31 AM, Conal Elliott <[EMAIL PROTECTED]> wrote:
> Hi Steve,
>
> Thanks for letting me know about the LANGUAGE problem.  Yes, I used
> 6.8-friendly (6.6-unfriendly) LANGUAGE pragmas.  In retrospect, probably not
> such a great idea, since there seem to be many folks still on 6.6.
>
> I just changed the sources (commenting out the LANGUAGE pragmas and
> inserting -fglasgow-exts pragmas), darcs-pushed, and put a new version (0.3)
> on hackage.  Please give it another try.
>
> Cheers, - Conal
>
>
>
> On Jan 18, 2008 7:58 PM, Steve Lihn <[EMAIL PROTECTED]> wrote:
> > Tried to install reactive-0.2 on GHC-6.6, but failed.
> >
> > Building reactive-0.2...
> > src/Data/Reactive.hs:1:13: cannot parse LANGUAGE pragma
> >
> > Is the package for GHC 6.8? Is there an older version (0.0?) for GHC
> > 6.6 that I can play with your example? (Or advise how to hack that
> > file to get it work on 6.6)
> >
> > Thanks,
> > Steve
> >
>
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] First go at reactive programming

2008-01-19 Thread Conal Elliott
Thanks for the TypeCompose>=0.3 tip. I've fixed my local Reactive.cabal and
will push at some point.

Oh yeay -- I'd forgotten about the "deriving" change in 6.8 vs 6.6.

Urg.  I didn't realize that 'forever' isn't in 6.2.  You can use the 6.8def:

-- | @'forever' act@ repeats the action infinitely.
forever :: (Monad m) => m a -> m ()
forever a   = a >> forever a

I'm wondering how hard to try to get these libs to work with both 6.6 and
6.8.  My hope has been that people will switch to 6.8, but perhaps there are
obstacles I don't know about.  Is there something that keeps you from
upgrading?

  - Conal

On Jan 19, 2008 6:14 AM, Steve Lihn <[EMAIL PROTECTED]> wrote:

> Reactive-0.3 seems to have a dependency on TypeCompose-0.3. Earlier
> version does not work (for lack of Data.Pair). This probably should be
> specified in Cabal file.
>
> I aslo fixed all the LANGUAGE problems and now encountered the
> following error in TypeCompose:
>
> [4 of 9] Compiling Control.Compose  ( src/Control/Compose.hs,
> dist/build/Control/Compose.o )
> src/Control/Compose.hs:561:0: parse error on input `deriving'
>
> I tried to restored the commented out "deriving Monoid" and got pass
> that. Not sure if that is right though. Back to reactive-0.3, I
> encountered:
>
> src/Data/Future.hs:60:27:
>Module `Control.Monad' does not export `forever'
>
> Forever is in the latest library, but not in my GHC 6.6. I am not sure
> how to get this fixed. Any suggestion?
>
>
> http://www.haskell.org/ghc/docs/latest/html/libraries/base/Control-Monad.html
>
>
> Steve
>
>
> On Jan 19, 2008 1:31 AM, Conal Elliott <[EMAIL PROTECTED]> wrote:
> > Hi Steve,
> >
> > Thanks for letting me know about the LANGUAGE problem.  Yes, I used
> > 6.8-friendly (6.6-unfriendly) LANGUAGE pragmas.  In retrospect, probably
> not
> > such a great idea, since there seem to be many folks still on 6.6.
> >
> > I just changed the sources (commenting out the LANGUAGE pragmas and
> > inserting -fglasgow-exts pragmas), darcs-pushed, and put a new version (
> 0.3)
> > on hackage.  Please give it another try.
> >
> > Cheers, - Conal
> >
> >
> >
> > On Jan 18, 2008 7:58 PM, Steve Lihn <[EMAIL PROTECTED]> wrote:
> > > Tried to install reactive-0.2 on GHC-6.6, but failed.
> > >
> > > Building reactive-0.2...
> > > src/Data/Reactive.hs:1:13: cannot parse LANGUAGE pragma
> > >
> > > Is the package for GHC 6.8? Is there an older version (0.0?) for GHC
> > > 6.6 that I can play with your example? (Or advise how to hack that
> > > file to get it work on 6.6)
> > >
> > > Thanks,
> > > Steve
> > >
> >
> >
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] First go at reactive programming

2008-01-19 Thread Steve Lihn
> -- | @'forever' act@ repeats the action infinitely.
> forever :: (Monad m) => m a -> m ()
> forever a   = a >> forever a

Great. The code compiled successfully by inserting this in various places.

> I'm wondering how hard to try to get these libs to work with both 6.6 and
> 6.8.  My hope has been that people will switch to 6.8, but perhaps there are
> obstacles I don't know about.  Is there something that keeps you from
> upgrading?

I am asking this question in another thread. The problem is -- I've
got many modules compiled under 6.6, some with much agony. If I switch
to 6.8, I have to recompile them again. Two issues I image:

(1) It may take lots of effort to recompile all the modules. I have
forgetten how I got around some of the modules! Too bad... Got to take
notes next time...
(2) If I got stuck in 6.8, it may not be easy to switch back.

It does not appear straightforward to me. I'd like to hear how other
people approach these issues before I jump into it. Don't want to
break the working environment that I spent months to set up!
--
Finally, get to test the Reactive sample code.

(1) Levi's first post compiled successfully and worked like charm. Congrat.
(2) Levi's second post did not compile. There is a type error...

react.hs:33:65:
Couldn't match expected type `Handle'
   against inferred type `RequestHandler'
In the first argument of `handleConnection', namely `r'
In the first argument of `fmap', namely `(handleConnection r)'
In the second argument of `(.)', namely `fmap (handleConnection r)'

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


Re: [Haskell-cafe] First go at reactive programming

2008-01-19 Thread gwern0
On 2008.01.19 12:22:43 -0500, Steve Lihn <[EMAIL PROTECTED]> scribbled 1.5K 
characters:
...
> I am asking this question in another thread. The problem is -- I've
> got many modules compiled under 6.6, some with much agony. If I switch
> to 6.8, I have to recompile them again. Two issues I image:
>
> (1) It may take lots of effort to recompile all the modules. I have
> forgetten how I got around some of the modules! Too bad... Got to take
> notes next time...

These days, every package you'd want to install (with the exception of GHC, 
Darcs, and the large graphics toolkits) should be available on Hackage or at 
least in Cabalized form.

If they aren't, then that's a bug or at least missing feature. The whole point 
of Cabal was so you don't have to take notes!

> (2) If I got stuck in 6.8, it may not be easy to switch back.

Well, uh, is that really a bad thing? Do you worry about device drivers 
'because if I got stuck in the 2.x series of Linux kernels, it may not be easy 
to switch back [to 1.x]'? No; 6.8.x is the future. The older GHCs will fall 
behind, people will rightfully upgrade, things will bitrot, and so on. There's 
no real benefit to willfully using outdated software - the most painful parts 
of the 6.8.x upgrade are past.

> It does not appear straightforward to me. I'd like to hear how other
> people approach these issues before I jump into it. Don't want to
> break the working environment that I spent months to set up!

I began darcs send'ing patches for stuff broken by 6.8.x; by this point, all 
the major stuff I use is fixed, at least out of Darcs (although many packages 
are woefully outdated on Hackage. I've been working on this).

...
> Thanks.
> Steve

--
gwern
Information II captain SAS BRLO unclassified of Audiotel Taiwan RSOC


pgpg7mEkHNDX2.pgp
Description: PGP signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] First go at reactive programming

2008-01-20 Thread Steve Lihn
This fixed the second example. Thanks.

>
> I think handleConnection should be
>
> handleConnection :: RequestHandler -> Handle -> IO ()
>
> handleConnection r h =
>  handleToRequest h >>= responseSend h . runRequestHandler r
>
>
> Levi
>
>
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe