Dynamic Source Loading

Donald Bruce Stewart dons at cse.unsw.edu.au
Mon Oct 25 23:29:37 EDT 2004


haskell:
> I am writing a web application server in Haskell.
> I would like to be able to modify the app on the
> fly.  Simplyfing the app server, it would look
> like this:
> 
>    appServer appMVar reqChan state =
>      do
>       req <- readChan reqChan
>       app <- readMVar appMVar
>       (state',resp) <- return $ app state req
>       forkIO $ doResp req resp
>       appServer appMVar reqChan state'
> 
> The app would get loaded as follows:
> 
>    updateApp writeLog appMVar moduleName fnName =
>       do
>         mbApp <- (getApp  >>= Just) `catch`
> 		 (\err -> writeLog err >> return Nothing)
>         maybe (return ()) (overWriteMVar appMVar) mbApp
> 	threadDelay 1000
> 	updateApp appMVar moduleName fnName
>       where
>         getApp = ghci_load_module moduleName >>=
> 		 flip  ghci_getName fnName
> 
>    overWriteMVar mvar val =
> 	if isEmptyMVar appMVar
>            then putMVar appMVar app
> 	   else swapMVar appMVar app
>         {-- Is there a way to overwrite an MVar
>             without risking blocking by another
>             thread filling it before the putMVar?
> 
> Note it would be really nice if:
> 
> * ghci_load_module would use an already
>   cached module if the underlying source file has
>   not changed (and therefore cost little
>   performance-wise).
> 
> * the returned code would be compiled with lots
>   of optimization, etc.
> 
> * Bonus: it would verify that the loaded function
>   is type consistent with channel but tolerate
>   bigger data types so that if the prior
>   app assumed state was
> 
>     data State = Foo | Bar
> 
>    It would not be an error if the new app handled
>    a state that looked like:
> 
>     data State = Foo | Bar | Baz
> 
> The result would be a haskell server where all the
> haskell source acts like asp, jsp, php pages, but
> its all type safe and you don't have to define a
> standard page type as in HSP.
> 
> I am aware that there is a DynamicLoader project:
> 
>   http://www.dtek.chalmers.se/~d00ram/dynamic/
> 
> That lets you load "object files."  But I would
> really like something that loads source files
> instead....

Please look at hs-plugins:
        http://www.cse.unsw.edu.au/~dons/hs-plugins

and the accompanying paper:
        http://www.cse.unsw.edu.au/~dons/hs-plugins/paper

hs-plugins is already being used at Chalmers for their Haskell Server
Pages project, which sounds a lot like what you're describing. You can
ask Niklas Broberg about this.

Cheers,
   Don


More information about the Glasgow-haskell-users mailing list