| Safe Haskell | None |
|---|
Language.Sunroof.Types
Description
The basic types and combinators of Sunroof.
- 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
- unJS :: JS t a -> (a -> Program (JSI t) ()) -> Program (JSI t) ()
- single :: JSI t a -> JS t a
- data JSI where
- JS_Assign :: Sunroof a => JSSelector a -> a -> JSObject -> JSI t ()
- JS_Select :: Sunroof a => JSSelector a -> JSObject -> JSI t a
- JS_Delete :: Sunroof a => JSSelector a -> JSObject -> JSI t ()
- JS_Invoke :: (SunroofArgument a, Sunroof r) => a -> JSFunction a r -> JSI t r
- JS_Eval :: Sunroof a => a -> JSI t a
- JS_Function :: (SunroofArgument a, Sunroof b) => (a -> JS A b) -> JSI t (JSFunction a b)
- JS_Continuation :: SunroofArgument a => (a -> JS B ()) -> JSI t (JSContinuation a)
- JS_Branch :: (SunroofThread t, Sunroof a, SunroofArgument a, Sunroof bool) => bool -> JS t a -> JS t a -> JSI t a
- JS_Return :: Sunroof a => a -> JSI t ()
- JS_Assign_ :: Sunroof a => Id -> a -> JSI t ()
- JS_Comment :: String -> JSI t ()
- JS_Fix :: SunroofArgument a => (a -> JS A a) -> JSI t a
- callcc :: SunroofArgument a => (JSContinuation a -> JS B a) -> JS B a
- done :: JS t a
- liftJS :: Sunroof a => JS A a -> JS t a
- kast :: SunroofArgument a => JSFunction a () -> JSContinuation a
- data JSFunction args ret
- data JSContinuation args
- function :: (SunroofArgument a, Sunroof b) => (a -> JS A b) -> JS t (JSFunction a b)
- continuation :: SunroofArgument a => (a -> JS B ()) -> JS t (JSContinuation a)
- goto :: forall args a t. SunroofArgument args => JSContinuation args -> args -> JS t a
- apply :: (SunroofArgument args, Sunroof ret) => JSFunction args ret -> args -> JS t ret
- ($$) :: (SunroofArgument args, Sunroof ret) => JSFunction args ret -> args -> JS t ret
- 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
- delete :: Sunroof a => JSSelector a -> JSObject -> JS t ()
- class Sunroof o => JSTuple o where
- class Sunroof key => SunroofKey key where
- jsKey :: key -> JSSelector a
Documentation
The possible threading models for Javascript computations.
data ThreadProxy t Source
A proxy to capture the type of threading model used.
See SunroofThread.
Constructors
| ThreadProxy |
class SunroofThread t whereSource
When implemented the type supports determining the threading model during runtime.
Methods
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.
Instances
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.
Constructors
| JS :: ((a -> Program (JSI t) ()) -> Program (JSI t) ()) -> JS t a | |
| := :: (Sunroof a, Sunroof o) => JSSelector a -> a -> o -> JS t () |
Instances
| 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) |
|
JSI represents the primitive effects or instructions for
the JS monad.
JS_Assign s v o- assigns a value
vto the selected fieldsin the objecto. JS_Select s o- returns the value of the selected field
sin the objecto. JS_Delete s o- delete the selected field
sin the objecto. JS_Invoke a f- calls the function
fwith the argumentsa. JS_Eval v- evaluates the value
v. Subsequent instructions use the value instead of reevaluating the expression. JS_Function f- creates a Javascript function
from the Haskell function
f. JS_Continuation f- creates a Javascript continuation (function that never returns a value)
from the Haskell function
f. JS_Branch b t f- creates a
if-then-elsestatement in Javascript. In that statementbis the condition,tis the true branch andfis the false branch. JS_Return v- translates into an actual
returnstatement that returns the valuevin Javascript. JS_Assign_ v x- assigns the value
xto the variable with namev. JS_Fix v x- models a fixpoint computation in
JS. Seejsfix.
Constructors
| JS_Assign :: Sunroof a => JSSelector a -> a -> JSObject -> JSI t () | |
| JS_Select :: Sunroof a => JSSelector a -> JSObject -> JSI t a | |
| JS_Delete :: Sunroof a => JSSelector a -> JSObject -> JSI t () | |
| JS_Invoke :: (SunroofArgument a, Sunroof r) => a -> JSFunction a r -> JSI t r | |
| JS_Eval :: Sunroof a => a -> JSI t a | |
| JS_Function :: (SunroofArgument a, Sunroof b) => (a -> JS A b) -> JSI t (JSFunction a b) | |
| JS_Continuation :: SunroofArgument a => (a -> JS B ()) -> JSI t (JSContinuation a) | |
| JS_Branch :: (SunroofThread t, Sunroof a, SunroofArgument a, Sunroof bool) => bool -> JS t a -> JS t a -> JSI t a | |
| JS_Return :: Sunroof a => a -> JSI t () | |
| JS_Assign_ :: Sunroof a => Id -> a -> JSI t () | |
| JS_Comment :: String -> JSI t () | |
| JS_Fix :: SunroofArgument a => (a -> JS A a) -> JSI t a |
callcc :: SunroofArgument a => (JSContinuation a -> JS B a) -> JS B aSource
Reify the current contination as a Javascript continuation
kast :: SunroofArgument a => JSFunction a () -> JSContinuation aSource
kast is cast to continuation. k is the letter often used to signify a continuation.
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.
Instances
| 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.
Instances
| 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 |
function :: (SunroofArgument a, Sunroof b) => (a -> JS A b) -> JS t (JSFunction a b)Source
Create an Atomic Javascript function from a Haskell function.
continuation :: SunroofArgument a => (a -> JS B ()) -> JS t (JSContinuation a)Source
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.
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.
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.
delete :: Sunroof a => JSSelector a -> JSObject -> JS t ()Source
o # delete lab removes the label lab from the object o.
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
Instances
| 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.
Methods
jsKey :: key -> JSSelector aSource
Instances