[Haskell-cafe] Summer of Code idea: Haskell Web Toolkit

Christopher Done chrisdone at googlemail.com
Tue Mar 6 23:38:26 CET 2012


I might as well chime in on this thread as it is relevant to my
interests. I made a write up on a comparison of HJScript (JavaScript
EDSL) and my Ji (control browser from Haskell) library:
https://github.com/chrisdone/ji

HJScript is "OK", hpaste.org uses it here:
https://github.com/chrisdone/amelie/blob/master/src/Amelie/View/Script.hs
output here: http://hpaste.org/js/amelie.js

Mini-summary of my experience: You're still stuck with JS semantics,
and it can be a little odd when you confuse what level of code (JS or
HS) you're working at, but at least it works right now and can be
well-typed. The library needs a bit of an overhaul, the GADT of
HJavaScript is simply flawed (take a brief look and you can see it can
express totally invalid JS in the syntax tree and the pretty printer
breaks operator/parens), but HJScript sorts the latter out, and I
would make all HJScript's functions generic upon MonadJS or something,
if you want a reader transformer or whatnot (i.e. to carry around some
state, a JS "object"), it breaks down with any higher-order
combinators taking actions as arguments. I also had some problems
making things generic AND type-accurate, but I don't recall them well
enough now. Problems aside, At Least It's Partially Well Typed.

I tried UHC out recently, made a little API for the canvas tag and
drew some pretty things. Had a little trouble with timers, though… the
callback for the timer /worked/, but the alert[1] printed the same
thing every time, as if the thunk forcing is somehow broken. I looked
at the outputted code but couldn't quite grok what was wrong with it.
Didn't get more time to investigate why. It may just be my code but it
looks sound to me, though I'm mostly winging it with the HTML5 part.

Anyway, look forward to watching ideas and work in this area.

Ciao!

[1]:

module Main where

import Control.Monad
import Language.UHC.JScript.Assorted
import Language.UHC.JScript.W3C.HTML5
import Language.UHC.JScript.ECMA.String
import Language.UHC.JScript.ECMA.Date
import Language.UHC.JScript.Types
import Language.UHC.JScript.Primitives
import Data.IORef

main = do
  doc <- document
  bodies <- documentGetElementsByTagName doc (toJS "canvas")
  body <- nodeListItem bodies 0
  ctx <- getContext body "2d"
  setFillStyle ctx "rgb(200,0,0)"
  start <- newIORef 0
  setInterval 1000 $ do
    st <- readIORef start
    forM_ [st..st+30] $ \i -> do
      let ir = fromIntegral i
      fillRect ctx (20 + 10*round (sin ir)) (i*10) 2 2
    writeIORef start (st + 1)
    alert (show st)
  return ()

In HTML5.hs:

data Timer

foreign import jscript "setInterval(%*)"
  _setInterval :: FunPtr (IO ()) -> Int -> IO Timer

foreign import jscript "wrapper"
  makeIntervalCallback :: IO () -> IO (FunPtr (IO ()))

setInterval delay haskellCallback = do
  jsCallback <- makeIntervalCallback haskellCallback
  _setInterval jsCallback delay



More information about the Haskell-Cafe mailing list