Calling convention for JavaScript?

Luite Stegeman stegeman at gmail.com
Wed Mar 20 06:47:42 CET 2013


On Mon, Mar 18, 2013 at 8:34 AM, Edward Z. Yang <ezyang at mit.edu> wrote:
> My guess is that you're out of luck without extending FFI to support
> another convention.  Here's a possible workaround, however: continue to
> use ccall import syntax, but provide the extra information you wanted
> to convey in the name out-of-band.

I've been thinking about this before, but I haven't found a good way
to do that yet, other than with Template Haskell. The point of the
inline JavaScript macros in particular is to give users a concise and
orderly way to do more complex imports, without external files. We
generate code from StgSyn, so that's pretty much the information we
have from the source file.

I talked with Duncan in #ghc and it looks like it's easy to add
another calling convention. Since GHCJS requires HEAD anyway (aiming
for a release on hackage when GHC 7.8.1 comes out) I'll make some
patches.

The result should look something like this:

-- calculate the hyperbolic tangent
foreign import javascript "var x = 2*$1; $r = Math.exp(x-1)/Math.exp(x+1);"
      js_tanh :: Double -> Double

-- copy part of a byte array
foreign import javascript "for(var i=0;i<$5;i++) { $3[i+$4] = $1[i+$2]; }"
      js_copyArray :: ByteArray# -> Int -> ByteArray# -> Int -> Int -> IO ()

-- do an async AJAX request with jQuery, return the status code
-- the current Haskell thread is suspended (in interruptible state)
-- until $c is called
foreign import safe javascript
         "jQuery.get(h$decodeUtf8z($1_1,$1_2))\
          \           .done(function(d,status) { $c(parseInt(status,10)); })\
          \           .fail(function() { $c(-1); });"
    js_ajaxStatus :: CString -> IO Int

main = do
  withCString "http://haskell.org/" $ \url -> do
    mstatus <- timeout 1000000 $ js_ajaxStatus url
    putStrLn $ maybe "server took too long to respond"
                                 (\x -> "http status: " ++ show x) mstatus

Comments welcome!

notes:
1. local variables declared in the javascript import macros are
converted to unique names in the resulting code
2. safe imports can perform asynchronous actions, following the
familiar callback pattern in JavaScript. They can also start new
Haskell threads (and wait for their results) or otherwise interact
with the GHCJS green thread scheduler. They're internally implemented
with an MVar, a waiting thread can still receive async exceptions.
3. all of this, other than the "foreign import javacript" part already
works, i pushed changes for adding threading, async exceptions and
async ffi to the github repository this week.

luite

p.s. sorry Edward for sending the mail only to your address first



More information about the ghc-devs mailing list