| Copyright | (c) The University of Glasgow 2001 | 
|---|---|
| License | BSD-style (see the file LICENSE) | 
| Maintainer | Jeffrey Young <jeffrey.young@iohk.io> Luite Stegeman <luite.stegeman@iohk.io> Sylvain Henry <sylvain.henry@iohk.io> Josh Meredith <josh.meredith@iohk.io> | 
| Stability | experimental | 
| Safe Haskell | Safe-Inferred | 
| Language | Haskell2010 | 
GHC.JS.Make
Description
- Domain and Purpose - GHC.JS.Make defines helper functions to ease the creation of JavaScript ASTs as defined in - Syntax. Its purpose is twofold: make the EDSL more ergonomic to program in, and make errors in the EDSL look obvious because the EDSL is untyped. It is primarily concerned with injecting terms into the domain of the EDSL to construct JS programs in Haskell.
- Strategy - The strategy for this module comes straight from gentzen; where we have two types of helper functions. Functions which inject terms into the EDSL, and combinator functions which operate on terms in the EDSL to construct new terms in the EDSL. Crucially, missing from this module are corresponding elimination or destructing functions which would project information from the EDSL back to Haskell. See - UnitUtilsand- CoreUtilsfor such functions.- Introduction functions - We define various primitive helpers which introduce terms in the EDSL, for example - jVar,- jLam, and- varand- jString. Notice that the type of each of these functions have the domain- isSat a => a -> ...; indicating that they each take something that can be injected into the EDSL domain, and the range- JExpror- JStat; indicating the corresponding value in the EDSL domain. Similarly this module exports two typeclasses- ToExprand- ToSat,- ToExprinjects values as a JS expression into the EDSL.- ToSatensures that terms introduced into the EDSL carry identifier information so terms in the EDSL must have meaning.
- Combinator functions - The rest of the module defines combinators which create terms in the EDSL from terms in the EDSL. Notable examples are - |=and- ||=,- |=is sugar for- AssignStat, it is a binding form that declares- foo = barassuming foo has been already declared.- ||=is more sugar on top of- |=, it is also a binding form that declares the LHS of- |=before calling- |=to bind a value, bar, to a variable foo. Other common examples are the- if_and- math_helpers such as- math_cos.
 
- Consumers - The entire JS backend consumes this module, e.g., the modules in GHC.StgToJS.*. 
- Notation - In this module we use - ==>in docstrings to show the translation from the JS EDSL domain to JS code. For example,- foo ||= bar ==> var foo; foo = bar;should be read as- foo ||= baris in the EDSL domain and results in the JS code- var foo; foo = bar;when compiled.
Synopsis
- class ToJExpr a where- toJExpr :: a -> JExpr
- toJExprFromList :: [a] -> JExpr
 
- class ToStat a where
- var :: FastString -> JExpr
- jString :: FastString -> JExpr
- jLam :: ToSat a => a -> JExpr
- jVar :: ToSat a => a -> JStat
- jFor :: (ToJExpr a, ToStat b) => JStat -> a -> JStat -> b -> JStat
- jForIn :: ToSat a => JExpr -> (JExpr -> a) -> JStat
- jForEachIn :: ToSat a => JExpr -> (JExpr -> a) -> JStat
- jTryCatchFinally :: ToSat a => JStat -> a -> JStat -> JStat
- (||=) :: Ident -> JExpr -> JStat
- (|=) :: JExpr -> JExpr -> JStat
- (.==.) :: JExpr -> JExpr -> JExpr
- (.===.) :: JExpr -> JExpr -> JExpr
- (.!=.) :: JExpr -> JExpr -> JExpr
- (.!==.) :: JExpr -> JExpr -> JExpr
- (.!) :: JExpr -> JExpr -> JExpr
- (.>.) :: JExpr -> JExpr -> JExpr
- (.>=.) :: JExpr -> JExpr -> JExpr
- (.<.) :: JExpr -> JExpr -> JExpr
- (.<=.) :: JExpr -> JExpr -> JExpr
- (.<<.) :: JExpr -> JExpr -> JExpr
- (.>>.) :: JExpr -> JExpr -> JExpr
- (.>>>.) :: JExpr -> JExpr -> JExpr
- (.|.) :: JExpr -> JExpr -> JExpr
- (.||.) :: JExpr -> JExpr -> JExpr
- (.&&.) :: JExpr -> JExpr -> JExpr
- if_ :: JExpr -> JExpr -> JExpr -> JExpr
- if10 :: JExpr -> JExpr
- if01 :: JExpr -> JExpr
- ifS :: JExpr -> JStat -> JStat -> JStat
- ifBlockS :: JExpr -> [JStat] -> [JStat] -> JStat
- jwhenS :: JExpr -> JStat -> JStat
- app :: FastString -> [JExpr] -> JExpr
- appS :: FastString -> [JExpr] -> JStat
- returnS :: JExpr -> JStat
- loop :: JExpr -> (JExpr -> JExpr) -> (JExpr -> JStat) -> JStat
- loopBlockS :: JExpr -> (JExpr -> JExpr) -> (JExpr -> [JStat]) -> JStat
- preIncrS :: JExpr -> JStat
- postIncrS :: JExpr -> JStat
- preDecrS :: JExpr -> JStat
- postDecrS :: JExpr -> JStat
- off8 :: JExpr -> JExpr -> JExpr
- off16 :: JExpr -> JExpr -> JExpr
- off32 :: JExpr -> JExpr -> JExpr
- off64 :: JExpr -> JExpr -> JExpr
- mask8 :: JExpr -> JExpr
- mask16 :: JExpr -> JExpr
- signExtend8 :: JExpr -> JExpr
- signExtend16 :: JExpr -> JExpr
- typeof :: JExpr -> JExpr
- returnStack :: JStat
- assignAllEqual :: HasDebugCallStack => [JExpr] -> [JExpr] -> JStat
- assignAll :: [JExpr] -> [JExpr] -> JStat
- assignAllReverseOrder :: [JExpr] -> [JExpr] -> JStat
- declAssignAll :: [Ident] -> [JExpr] -> JStat
- nullStat :: JStat
- (.^) :: JExpr -> FastString -> JExpr
- trace :: ToJExpr a => a -> JStat
- jhEmpty :: Map k JExpr
- jhSingle :: (Ord k, ToJExpr a) => k -> a -> Map k JExpr
- jhAdd :: (Ord k, ToJExpr a) => k -> a -> Map k JExpr -> Map k JExpr
- jhFromList :: [(FastString, JExpr)] -> JVal
- null_ :: JExpr
- undefined_ :: JExpr
- false_ :: JExpr
- true_ :: JExpr
- zero_ :: JExpr
- one_ :: JExpr
- two_ :: JExpr
- three_ :: JExpr
- math_log :: [JExpr] -> JExpr
- math_sin :: [JExpr] -> JExpr
- math_cos :: [JExpr] -> JExpr
- math_tan :: [JExpr] -> JExpr
- math_exp :: [JExpr] -> JExpr
- math_acos :: [JExpr] -> JExpr
- math_asin :: [JExpr] -> JExpr
- math_atan :: [JExpr] -> JExpr
- math_abs :: [JExpr] -> JExpr
- math_pow :: [JExpr] -> JExpr
- math_sqrt :: [JExpr] -> JExpr
- math_asinh :: [JExpr] -> JExpr
- math_acosh :: [JExpr] -> JExpr
- math_atanh :: [JExpr] -> JExpr
- math_cosh :: [JExpr] -> JExpr
- math_sinh :: [JExpr] -> JExpr
- math_tanh :: [JExpr] -> JExpr
- math_expm1 :: [JExpr] -> JExpr
- math_log1p :: [JExpr] -> JExpr
- math_fround :: [JExpr] -> JExpr
- decl :: Ident -> JStat
- allocData :: Int -> JExpr
- allocClsA :: Int -> JExpr
- dataFieldName :: Int -> FastString
- dataFieldNames :: [FastString]
Injection Type classes
The ToJExpr class handles injection of of things into the EDSL as a JS
 expression
class ToJExpr a where Source #
Things that can be marshalled into javascript values. Instantiate for any necessary data structures.
Minimal complete definition
Instances
The ToStat class handles injection of of things into the EDSL as a JS
 statement. This ends up being polymorphic sugar for JS blocks, see helper
 function expr2stat. Instantiate for any necessary data
 structures.
Introduction functions
var :: FastString -> JExpr Source #
construct a JS variable reference
jString :: FastString -> JExpr Source #
Convert a ShortText to a Javascript String
jLam :: ToSat a => a -> JExpr Source #
Create a new anonymous function. The result is a JExpr
 expression.
 Usage:
jLam $ \x -> jVar x + one_ jLam $ \f -> (jLam $ \x -> (f `app` (x `app` x))) `app` (jLam $ \x -> (f `app` (x `app` x)))
jVar :: ToSat a => a -> JStat Source #
Introduce a new variable into scope for the duration of the enclosed expression. The result is a block statement. Usage:
jVar $ x y -> mconcat [jVar x ||= one_, jVar y ||= two_, jVar x + jVar y]
jForIn :: ToSat a => JExpr -> (JExpr -> a) -> JStat Source #
Create a 'for in' statement. Usage:
jForIn {expression} $ x -> {block involving x}jForEachIn :: ToSat a => JExpr -> (JExpr -> a) -> JStat Source #
As with "jForIn" but creating a "for each in" statement.
jTryCatchFinally :: ToSat a => JStat -> a -> JStat -> JStat Source #
As with "jForIn" but creating a "for each in" statement.
Combinators
Combinators operate on terms in the JS EDSL domain to create new terms in the EDSL domain.
(||=) :: Ident -> JExpr -> JStat infixl 2 Source #
Declare a variable and then Assign the variable to an expression
foo |= expr ==> var foo; foo = expr;
(|=) :: JExpr -> JExpr -> JStat infixl 2 Source #
Assign a variable to an expression
foo |= expr ==> var foo = expr;
(.!) :: JExpr -> JExpr -> JExpr infixl 8 Source #
return the expression at idx of obj
obj .! idx ==> obj[idx]
if10 :: JExpr -> JExpr Source #
if-expression that returns 1 if condition = true, 0 otherwise
if10 e ==> e ? 1 : 0
if01 :: JExpr -> JExpr Source #
if-expression that returns 0 if condition = true, 1 otherwise
if01 e ==> e ? 0 : 1
ifS :: JExpr -> JStat -> JStat -> JStat Source #
If-expression which returns statements, see related ifBlockS
if e s1 s2 ==> if(e) { s1 } else { s2 }ifBlockS :: JExpr -> [JStat] -> [JStat] -> JStat Source #
If-expression which returns blocks
ifBlockS e s1 s2 ==> if(e) { s1 } else { s2 }jwhenS :: JExpr -> JStat -> JStat Source #
A when-statement as syntactic sugar via ifS
jwhenS cond block ==> if(cond) { block } else {  }app :: FastString -> [JExpr] -> JExpr Source #
an expression application, see related appS
app f xs ==> f(xs)
loop :: JExpr -> (JExpr -> JExpr) -> (JExpr -> JStat) -> JStat Source #
"for" loop with increment at end of body
loopBlockS :: JExpr -> (JExpr -> JExpr) -> (JExpr -> [JStat]) -> JStat Source #
"for" loop with increment at end of body
signExtend8 :: JExpr -> JExpr Source #
Sign-extend/narrow a 8-bit value
signExtend16 :: JExpr -> JExpr Source #
Sign-extend/narrow a 16-bit value
returnStack :: JStat Source #
assignAllEqual :: HasDebugCallStack => [JExpr] -> [JExpr] -> JStat Source #
(.^) :: JExpr -> FastString -> JExpr infixl 8 Source #
Select a property prop, from and object obj
obj .^ prop ==> obj.prop
Hash combinators
jhAdd :: (Ord k, ToJExpr a) => k -> a -> Map k JExpr -> Map k JExpr Source #
insert a key-value pair into a JS HashMap
jhFromList :: [(FastString, JExpr)] -> JVal Source #
Construct a JS HashMap from a list of key-value pairs
Literals
Literals in the JS EDSL are constants in the Haskell domain. These are useful helper values and never change
undefined_ :: JExpr Source #
The JS literal undefined
Math functions
Math functions in the EDSL are literals, with the exception of math_ which
 is the sole math introduction function.
math_asinh :: [JExpr] -> JExpr Source #
math_acosh :: [JExpr] -> JExpr Source #
math_atanh :: [JExpr] -> JExpr Source #
math_expm1 :: [JExpr] -> JExpr Source #
math_log1p :: [JExpr] -> JExpr Source #
math_fround :: [JExpr] -> JExpr Source #
Statement helpers
Miscellaneous
Everything else,
dataFieldName :: Int -> FastString Source #
dataFieldNames :: [FastString] Source #