sunroof-compiler-0.2: Monadic Javascript Compiler

Safe HaskellNone

Language.Sunroof.Compiler

Description

Provides the Sunroof to Javascript compiler.

Synopsis

Documentation

sunroofCompileJSA :: Sunroof a => CompilerOpts -> String -> JS A a -> IO StringSource

The sunroof compiler compiles an effect that returns a Sunroof/JavaScript value into a JavaScript program. An example invocation is

 GHCi> import Language.Sunroof
 GHCi> import Language.Sunroof.JS.Browser
 GHCi> import Data.Default
 GHCi> txt <- sunroofCompileJSA def "main" $ do alert(js "Hello");
 GHCi> putStrLn txt
 var main = (function() {
   alert("Hello");
 })();

(The extra function and application are intentional and are a common JavaScript trick to circumvent scoping issues.)

To generate a function, not just an effect, you can use the function combinator.

 GHCi> txt <- sunroofCompileJSA def "main" $ do
            function $ \ n -> do
                return (n * (n :: JSNumber))
 GHCi> putStrLn txt
 var main = (function() {
   var v1 = function(v0) {
     return v0*v0;
   };
   return v1;
 })();

Now main in JavaScript is bound to the square function.

sunroofCompileJSB :: CompilerOpts -> String -> JS B () -> IO StringSource

Compiles code using the blocking threading model. Usage is the same as for sunroofCompileJSA.

compileJS :: CompilerOpts -> Uniq -> (a -> JS t ()) -> JS t a -> IO ([Stmt], Uniq)Source

Compile a Javascript computation (using the given continuation closer) into basic Javascript statements. Also return the next fresh unique. This function should only be used if you know what your doing!

data CompilerOpts Source

Options to setup the compiler.

Constructors

CompilerOpts 

Fields

co_on :: Bool

Do we reify to capture Haskell-level lets / CSEs?

co_cse :: Bool

Do we also capture non-reified CSE, using Value Numbering?

co_const :: Bool

Do we constant fold?

co_verbose :: Int

How verbose is the compiler when running? standard 0 - 3 scale

co_compress :: Bool

Does the compiler output code without whitespace and layout? default == False

Instances

Show CompilerOpts 
Default CompilerOpts

Default compiler options.