Safe Haskell | None |
---|
Sunroof provides a way to express Javascript computations in
Haskell. The computations can be expressed using the JS
monad.
There are ready to use API bindings for frequently used Javascript:
-
Browser
- Bindings of the standard browser APIs. -
Canvas
- Bindings of the HTML5 canvas element API. -
JQuery
- Bindings of some JQuery methods. -
Date
- Bindings of the standard data API.
It also provides an abstraction over Javascripts (not existing) threading
model. Cooperative multithreading can be emulated using the Sunroof
abstractions (forkJS
, yield
, loop
). Equivalents of well-known
Haskell concurrency abstractions like MVar
or Chan
are also provided on Javascript level
through JSMVar
and JSChan
.
Due to the threading abstraction there are two kinds of computations.
They are indicated by the first type parameter of JS
(a T
value).
Normal Javascript computations that can be assumed to terminate and
that may deliver a result value are written in the JSA
monad. While
possibly blocking computations (those that involve threading operations)
are written in the JSB
monad.
As the computations are expressed in Haskell, they have a functional
nature. It is possible to change the attribute values of objects using
:=
and #
:
o # att := val
If a top-level mutable variable is needed, use the JSRef
abstraction.
It is comparable to IORef
.
- sunroofCompileJSA :: Sunroof a => CompilerOpts -> String -> JS A a -> IO String
- sunroofCompileJSB :: CompilerOpts -> String -> JS B () -> IO String
- data CompilerOpts = CompilerOpts {
- co_on :: Bool
- co_cse :: Bool
- co_const :: Bool
- co_verbose :: Int
- co_compress :: Bool
- class Sunroof a where
- class SunroofValue a where
- class SunroofArgument args where
- class Sunroof o => JSTuple o where
- class Sunroof key => SunroofKey key where
- jsKey :: key -> JSSelector a
- data Type
- data T
- data ThreadProxy t = ThreadProxy
- class SunroofThread t where
- evalStyle :: ThreadProxy t -> T
- blockableJS :: Sunroof a => JS t a -> JS B a
- data JS where
- type JSA a = JS A a
- type JSB a = JS B a
- data JSFunction args ret
- data JSContinuation args
- data JSSelector a
- done :: JS t a
- liftJS :: Sunroof a => JS A a -> JS t a
- function :: (SunroofArgument a, Sunroof b) => (a -> JS A b) -> JS t (JSFunction a b)
- continuation :: SunroofArgument a => (a -> JS B ()) -> JS t (JSContinuation a)
- apply :: (SunroofArgument args, Sunroof ret) => JSFunction args ret -> args -> JS t ret
- ($$) :: (SunroofArgument args, Sunroof ret) => JSFunction args ret -> args -> JS t ret
- goto :: forall args a t. SunroofArgument args => JSContinuation args -> args -> JS t a
- cast :: (Sunroof a, Sunroof b) => a -> b
- (#) :: a -> (a -> JS t b) -> JS t b
- attr :: String -> JSSelector a
- fun :: (SunroofArgument a, Sunroof r) => String -> JSFunction a r
- invoke :: (SunroofArgument a, Sunroof r, Sunroof o) => String -> a -> o -> JS t r
- new :: SunroofArgument a => String -> a -> JS t JSObject
- evaluate :: Sunroof a => a -> JS t a
- value :: Sunroof a => a -> JS t a
- switch :: (EqB a, BooleanOf a ~ JSBool, Sunroof a, Sunroof b, SunroofArgument b, SunroofThread t) => a -> [(a, JS t b)] -> JS t b
- nullJS :: JSObject
- label :: JSString -> JSSelector a
- index :: JSNumber -> JSSelector a
- (!) :: forall o a. (Sunroof o, Sunroof a) => o -> JSSelector a -> a
- callcc :: SunroofArgument a => (JSContinuation a -> JS B a) -> JS B a
- comment :: String -> JS t ()
- delete :: Sunroof a => JSSelector a -> JSObject -> JS t ()
- forkJS :: SunroofThread t1 => JS t1 () -> JS t2 ()
- threadDelay :: JSNumber -> JSB ()
- yield :: JSB ()
- data JSObject
- this :: JSObject
- object :: String -> JSObject
- data JSBool
- data JSNumber
- int :: Sunroof a => a -> JSNumber
- data JSString
- string :: String -> JSString
- data JSArray a
- array :: (SunroofValue a, Sunroof (ValueOf a)) => [a] -> JS t (JSArray (ValueOf a))
- newArray :: (SunroofArgument args, Sunroof a) => args -> JS t (JSArray a)
- length' :: JSSelector JSNumber
- lookup' :: Sunroof a => JSNumber -> JSArray a -> a
- insert' :: Sunroof a => JSNumber -> a -> JSArray a -> JS t ()
- shift :: Sunroof a => JSArray a -> JS t a
- unshift :: (SunroofArgument a, Sunroof a) => a -> JSArray a -> JS t ()
- pop :: Sunroof a => JSArray a -> JS t a
- push :: (SunroofArgument a, Sunroof a) => a -> JSArray a -> JS t ()
- forEach :: (Sunroof a, SunroofArgument a) => (a -> JS A ()) -> JSArray a -> JS t ()
- empty :: Sunroof a => JS t (JSArray a)
- data JSRef a
- newJSRef :: Sunroof a => a -> JS t (JSRef a)
- readJSRef :: Sunroof a => JSRef a -> JS t a
- writeJSRef :: Sunroof a => a -> JSRef a -> JS t ()
- modifyJSRef :: Sunroof a => (a -> JS A a) -> JSRef a -> JS t ()
- data JSChan a
- newChan :: SunroofArgument a => JS t (JSChan a)
- writeChan :: forall t a. (SunroofThread t, SunroofArgument a) => a -> JSChan a -> JS t ()
- readChan :: forall a. (Sunroof a, SunroofArgument a) => JSChan a -> JS B a
- data JSMVar a
- newMVar :: forall a t. SunroofArgument a => a -> JS t (JSMVar a)
- newEmptyMVar :: SunroofArgument a => JS t (JSMVar a)
- takeMVar :: forall a. (Sunroof a, SunroofArgument a) => JSMVar a -> JS B a
- putMVar :: forall a. SunroofArgument a => a -> JSMVar a -> JS B ()
- loop :: Sunroof a => a -> (a -> JSB a) -> JSB ()
- fixJS :: SunroofArgument a => (a -> JSA a) -> JS t a
Notes
It is advised to use Sunroof with the following language extensions:
-
OverloadedStrings
- Enables using literal strings for attribute names and Javascript strings. -
DataKinds
- Enables usingJS A
orJS B
instead ofJSA
andJSB
. This extension is not essential.
Sunroof Compiler
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
.
data CompilerOpts Source
Options to setup the compiler.
CompilerOpts | |
|
Show CompilerOpts | |
Default CompilerOpts | Default compiler options. |
Classes
Central type class of Sunroof. Every type that can be translated into Javascript with Sunroof has to implement this type class.
Create a Sunroof value from a plain Javascript expression.
Reveal the plain Javascript expression that represents this Sunroof value.
typeOf :: Proxy a -> TypeSource
Returns the type of Javascript expression this Sunroof value
represents. The default implementation returns Base
as type.
Sunroof () | Unit is a Sunroof value. It can be viewed as a representation
of |
Sunroof JSBool | |
Sunroof JSObject | |
Sunroof JSNumber | First-class values in Javascript. |
Sunroof JSString | First-class Javascript value. |
Sunroof JSConsole | First-class values in Javascript. |
Sunroof JSDate | First-class values in Javascript. |
Sunroof JSCanvas | First-class values in Javascript. |
SunroofArgument a => Sunroof (JSContinuation a) | Functions are first-class citizens of Javascript. Therefore they
are |
Sunroof a => Sunroof (JSRef a) | |
Sunroof a => Sunroof (JSArray a) | Arrays are first-class Javascript values. |
SunroofArgument o0 => Sunroof (JSChan o0) | |
SunroofArgument o0 => Sunroof (JSMVar o0) | |
(SunroofArgument a, Sunroof r) => Sunroof (JSFunction a r) | Functions are first-class citizens of Javascript. Therefore they
are |
(SunroofKey k, Sunroof a) => Sunroof (JSMap k a) |
class SunroofValue a whereSource
All Haskell values that have a Sunroof representation implement this class.
SunroofValue Bool | |
SunroofValue Char | |
SunroofValue Double | |
SunroofValue Float | |
SunroofValue Int | |
SunroofValue Integer | |
SunroofValue () | Unit is unit. |
SunroofValue [Char] | |
Integral a => SunroofValue (Ratio a) | |
SunroofArgument a => SunroofValue (a -> JS B ()) |
|
(SunroofArgument a, Sunroof b) => SunroofValue (a -> JS A b) |
|
class SunroofArgument args whereSource
Everything that can be used as argument to a function is Javascript/Sunroof.
jsArgs :: args -> [Expr]Source
Turn the argument into a list of expressions.
jsValue :: UniqM m => m argsSource
Create a list of fresh variables for the arguments.
typesOf :: Proxy args -> [Type]Source
Get the type of the argument values.
SunroofArgument () | Unit is the empty argument list. |
Sunroof a => SunroofArgument a | Every |
(Sunroof a, Sunroof b) => SunroofArgument (a, b) | Two arguments. |
(Sunroof a, Sunroof b, Sunroof c) => SunroofArgument (a, b, c) | Three arguments. |
(Sunroof a, Sunroof b, Sunroof c, Sunroof d) => SunroofArgument (a, b, c, d) | Four arguments. |
(Sunroof a, Sunroof b, Sunroof c, Sunroof d, Sunroof e) => SunroofArgument (a, b, c, d, e) | Five arguments. |
(Sunroof a, Sunroof b, Sunroof c, Sunroof d, Sunroof e, Sunroof f) => SunroofArgument (a, b, c, d, e, f) | Six arguments. |
(Sunroof a, Sunroof b, Sunroof c, Sunroof d, Sunroof e, Sunroof f, Sunroof g) => SunroofArgument (a, b, c, d, e, f, g) | Seven arguments. |
(Sunroof a, Sunroof b, Sunroof c, Sunroof d, Sunroof e, Sunroof f, Sunroof g, Sunroof h) => SunroofArgument (a, b, c, d, e, f, g, h) | Eight arguments. |
(Sunroof a, Sunroof b, Sunroof c, Sunroof d, Sunroof e, Sunroof f, Sunroof g, Sunroof h, Sunroof i) => SunroofArgument (a, b, c, d, e, f, g, h, i) | Nine arguments. |
class Sunroof o => JSTuple o whereSource
If something is a JSTuple
, it can easily be decomposed and
recomposed from different components. This is meant as a convenient
access to attributes of an object.
TODO: revisit this
JSTuple JSObject | |
SunroofArgument o0 => JSTuple (JSChan o0) | |
SunroofArgument o0 => JSTuple (JSMVar o0) |
class Sunroof key => SunroofKey key whereSource
Everything that can be used as an key in a dictionary lookup.
jsKey :: key -> JSSelector aSource
Types
Abstract types for Javascript expressions in Sunroof.
The possible threading models for Javascript computations.
data ThreadProxy t Source
A proxy to capture the type of threading model used.
See SunroofThread
.
class SunroofThread t whereSource
When implemented the type supports determining the threading model during runtime.
evalStyle :: ThreadProxy t -> TSource
Determine the used threading model captured the given ThreadProxy
object.
blockableJS :: Sunroof a => JS t a -> JS B aSource
Create a possibly blocking computation from the given one.
The monadic type of Javascript computations.
JS t a
is a computation using the thread model t
(see T
).
It returns a result of type a
.
JS :: ((a -> Program (JSI t) ()) -> Program (JSI t) ()) -> JS t a | |
:= :: (Sunroof a, Sunroof o) => JSSelector a -> a -> o -> JS t () |
Monad (JS t) | |
Functor (JS t) | |
(SunroofThread t, Sunroof a, SunroofArgument a) => IfB (JS t a) | |
Monoid (JS t ()) | |
Semigroup (JS t a) | We define the Semigroup instance for JS, where
the first result (but not the first effect) is discarded.
Thus, |
SunroofArgument a => SunroofValue (a -> JS B ()) |
|
(SunroofArgument a, Sunroof b) => SunroofValue (a -> JS A b) |
|
data JSFunction args ret Source
Type of Javascript functions.
The first type argument is the type of function argument.
This needs to be a instance of SunroofArgument
.
The second type argument of JSFunction
is the function return type.
It needs to be a instance of Sunroof
.
Show (JSFunction a r) | |
(SunroofArgument a, Sunroof r) => IfB (JSFunction a r) | Functions may be the result of a branch. |
(SunroofArgument a, Sunroof r) => Sunroof (JSFunction a r) | Functions are first-class citizens of Javascript. Therefore they
are |
data JSContinuation args Source
Type of Javascript functions.
The first type argument is the type of function argument.
This needs to be a instance of SunroofArgument
.
The second type argument of JSFunction
is the function return type.
It needs to be a instance of Sunroof
.
Show (JSContinuation a) | |
(SunroofArgument a, Sunroof r) => IfB (JSContinuation a) | Functions may be the result of a branch. |
SunroofArgument a => Sunroof (JSContinuation a) | Functions are first-class citizens of Javascript. Therefore they
are |
data JSSelector a Source
A JSSelector
selects a field or attribute from a Javascript object.
The phantom type is the type of the selected value. Note the selected
field or attributes may also array entries (index
).
Show (JSSelector a) | |
IsString (JSSelector a) | Selectors can be created from the name of their attribute. |
DSL Primitives and Utilties
function :: (SunroofArgument a, Sunroof b) => (a -> JS A b) -> JS t (JSFunction a b)Source
Create an A
tomic Javascript function from a Haskell function.
continuation :: SunroofArgument a => (a -> JS B ()) -> JS t (JSContinuation a)Source
apply :: (SunroofArgument args, Sunroof ret) => JSFunction args ret -> args -> JS t retSource
apply f a
applies the function f
to the given arguments a
.
A typical use case looks like this:
foo `apply` (x,y)
See $$
for a convenient infix operator to do this.
($$) :: (SunroofArgument args, Sunroof ret) => JSFunction args ret -> args -> JS t retSource
f $$ a
applies the function f
to the given arguments a
.
See apply
.
goto :: forall args a t. SunroofArgument args => JSContinuation args -> args -> JS t aSource
goto
calls the given continuation with the given argument,
and never returns.
cast :: (Sunroof a, Sunroof b) => a -> bSource
Cast one Sunroof value into another.
This is sometimes needed due to Javascripts flexible type system.
(#) :: a -> (a -> JS t b) -> JS t bSource
The #
-operator is the Haskell analog to the .
-operator
in Javascript. Example:
document # getElementById "bla"
This can be seen as equivalent of document.getElementById("bla")
.
attr :: String -> JSSelector aSource
Creates a selector for attributes of Javascript objects. It is advised to use this together with an associated type signature to avoid ambiguity. Example:
length :: JSSelector JSNumber length = attr "length"
Selectors can be used with !
.
fun :: (SunroofArgument a, Sunroof r) => String -> JSFunction a rSource
Create a binding to a Javascript top-level function with the given name. It is advised to create these bindings with an associated type signature to ensure type safty while using this function. Example:
alert :: JSFunction JSString () alert = fun "alert"
invoke :: (SunroofArgument a, Sunroof r, Sunroof o) => String -> a -> o -> JS t rSource
invoke s a o
calls the method with name s
using the arguments a
on the object o
. A typical use would look like this:
o # invoke "foo" (x, y)
Another use case is writing Javascript API bindings for common methods:
getElementById :: JSString -> JSObject -> JS t JSObject getElementById s = invoke "getElementById" s
Like this the flexible type signature gets fixed. See #
for how to use these bindings.
new :: SunroofArgument a => String -> a -> JS t JSObjectSource
new n a
calls the new operator on the constructor n
supplying the argument a
. A typical use would look like this:
new "Object" ()
evaluate :: Sunroof a => a -> JS t aSource
Evaluate a Sunroof
value. This forces evaluation
of the given expression to a value and enables binding it to a
variable. Example:
x <- evaluate $ "A" <> "B" alert x alert x
This would result in: var v0 = "A"+"B"; alert(v0); alert(v0);
. But:
x <- return $ "A" <> "B" alert x alert x
This will result in: alert("A"+"B"); alert("A"+"B");
.
switch :: (EqB a, BooleanOf a ~ JSBool, Sunroof a, Sunroof b, SunroofArgument b, SunroofThread t) => a -> [(a, JS t b)] -> JS t bSource
Combinator for switch
-like statements in Javascript.
Note: This will not be translated into actual switch statment, because you are aloud arbitrary expressions in the cases.
label :: JSString -> JSSelector aSource
Create a selector for a named field or attribute. For type safty it is adivsed to use this with an accompanying type signature. Example:
array ! label "length"
See !
for further information on usage.
index :: JSNumber -> JSSelector aSource
Create a selector for an indexed value (e.g. array access). For type safty it is adivsed to use this with an accompanying type signature. Example:
array ! index 4
See !
for further information on usage.
(!) :: forall o a. (Sunroof o, Sunroof a) => o -> JSSelector a -> aSource
Operator to use a selector on a Javascript object. Examples:
array ! label "length" array ! index 4
callcc :: SunroofArgument a => (JSContinuation a -> JS B a) -> JS B aSource
Reify the current contination as a Javascript continuation
delete :: Sunroof a => JSSelector a -> JSObject -> JS t ()Source
o # delete lab
removes the label lab
from the object o
.
Concurrency Primitives
forkJS :: SunroofThread t1 => JS t1 () -> JS t2 ()Source
Fork of the given computation in a different thread.
threadDelay :: JSNumber -> JSB ()Source
Delay the execution of all instructions after this one by the given amount of milliseconds.
Basic JS types
JavaScript Object
Data type for all Javascript objects.
Boolean
Booleans in Javascript.
Numbers
Type of numbers in Javascript.
Floating JSNumber | |
Fractional JSNumber | |
Num JSNumber | |
Show JSNumber | Show the Javascript |
NumB JSNumber | |
IntegralB JSNumber | |
RealFracB JSNumber | |
RealFloatB JSNumber | |
IfB JSNumber | |
EqB JSNumber | |
OrdB JSNumber | |
VectorSpace JSNumber | |
AdditiveGroup JSNumber | |
Sunroof JSNumber | First-class values in Javascript. |
SunroofKey JSNumber |
Strings
Javascript string type.
Show JSString | Show the Javascript. |
IsString JSString | Create them from Haskell |
IfB JSString | |
EqB JSString | Value equality. |
Monoid JSString | Monoid under concatination and empty string. |
Semigroup JSString | Semigroup under concatination. |
Sunroof JSString | First-class Javascript value. |
SunroofKey JSString |
Array
Type if arrays in Javascript. The type parameter given the entry type.
array :: (SunroofValue a, Sunroof (ValueOf a)) => [a] -> JS t (JSArray (ValueOf a))Source
Create a literal array from a Haskell list.
newArray :: (SunroofArgument args, Sunroof a) => args -> JS t (JSArray a)Source
Create a new array object containing the given values.
length' :: JSSelector JSNumberSource
The length
property of arrays.
insert' :: Sunroof a => JSNumber -> a -> JSArray a -> JS t ()Source
A type-safe version of array insert.
shift :: Sunroof a => JSArray a -> JS t aSource
Removes and return the first element of an array (dequeue). See http://www.w3schools.com/jsref/jsref_shift.asp.
unshift :: (SunroofArgument a, Sunroof a) => a -> JSArray a -> JS t ()Source
Adds a new element to the beginning of the array (queue). Returns nothing instead of the new length. See http://www.w3schools.com/jsref/jsref_unshift.asp.
pop :: Sunroof a => JSArray a -> JS t aSource
Pop a element from the array as if it was a stack. See http://www.w3schools.com/jsref/jsref_pop.asp.
push :: (SunroofArgument a, Sunroof a) => a -> JSArray a -> JS t ()Source
Push a element into the array as if it was a stack. Returns nothing instead of the new length. See http://www.w3schools.com/jsref/jsref_push.asp.
forEach :: (Sunroof a, SunroofArgument a) => (a -> JS A ()) -> JSArray a -> JS t ()Source
Foreach iteration method provided by most browsers. Execute the given action on each element of the array. See https://developer.mozilla.org/en-US/docs/JavaScript/Reference/Global_Objects/Array/forEach, http://msdn.microsoft.com/en-us/library/ie/ff679980.aspx.
References
This is the IORef
of Sunroof.
modifyJSRef :: Sunroof a => (a -> JS A a) -> JSRef a -> JS t ()Source
Non-blocking modification of a JSRef
.
Channnels
JSChan
abstraction. The type parameter gives
the type of values held in the channel.
SunroofArgument o0 => Show (JSChan o0) | |
SunroofArgument o0 => IfB (JSChan o0) | |
SunroofArgument o => EqB (JSChan o) | Reference equality, not value equality. |
SunroofArgument o0 => Sunroof (JSChan o0) | |
SunroofArgument o0 => JSTuple (JSChan o0) |
writeChan :: forall t a. (SunroofThread t, SunroofArgument a) => a -> JSChan a -> JS t ()Source
Put a value into the channel. This will never block.
readChan :: forall a. (Sunroof a, SunroofArgument a) => JSChan a -> JS B aSource
Take a value out of the channel. If there is no value inside, this will block until one is available.
Thread-safe Mutable Variables
SunroofArgument o0 => Show (JSMVar o0) | |
SunroofArgument o0 => IfB (JSMVar o0) | |
SunroofArgument o => EqB (JSMVar o) | Reference equality, not value equality. |
SunroofArgument o0 => Sunroof (JSMVar o0) | |
SunroofArgument o0 => JSTuple (JSMVar o0) |
newMVar :: forall a t. SunroofArgument a => a -> JS t (JSMVar a)Source
Create a new JSMVar
with the given value inside.
See newEmptyMVar
.
newEmptyMVar :: SunroofArgument a => JS t (JSMVar a)Source
takeMVar :: forall a. (Sunroof a, SunroofArgument a) => JSMVar a -> JS B aSource
Take the value out of the JSMVar
. If there is no value
inside, this will block until one is available.
putMVar :: forall a. SunroofArgument a => a -> JSMVar a -> JS B ()Source
Put the value into the JSMVar
. If there already is a
value inside, this will block until it is taken out.
DSL Utilties
loop :: Sunroof a => a -> (a -> JSB a) -> JSB ()Source
loop x f
executes the function f
repeatedly.
After each iteration the result value of the function
is feed back as input of the next iteration.
The initial value supplied for the first iteration is x
.
This loop will never terminate.
fixJS :: SunroofArgument a => (a -> JSA a) -> JS t aSource
jsfix
is the mfix
for the JS Monad.