|
| HJScript.Lang | | Stability | experimental
| | Maintainer | Joel Bjornson joel.bjornson@gmail.com,
Niklas Broberg nibro@cs.chalmers.se
|
|
|
|
| Description |
|
|
| Synopsis |
|
| preinc :: Num t => Var t -> HJScript () | | | postinc :: Num t => Var t -> HJScript () | | | predec :: Num t => Var t -> HJScript () | | | postdec :: Num t => Var t -> HJScript () | | | (.+.) :: PlusOpType a => HJSJBinOperator a a | | | (.-.) :: Num a => HJSJBinOperator a a | | | (.*.) :: Num a => HJSJBinOperator a a | | | (./.) :: Num a => HJSJBinOperator a a | | | (.&&.) :: HJSJBinOperator Bool Bool | | | (.||.) :: HJSJBinOperator Bool Bool | | | (.==.) :: HJSJBinOperator a Bool | | | (.!=.) :: HJSJBinOperator a Bool | | | (.>.) :: Num a => HJSJBinOperator a Bool | | | (.<.) :: Num a => HJSJBinOperator a Bool | | | (.>=.) :: Num a => HJSJBinOperator a Bool | | | (.<=.) :: Num a => HJSJBinOperator a Bool | | | (.=.) :: Var t -> Exp t -> HJScript () | | | (.+=.) :: Num t => Var t -> Exp t -> HJScript () | | | (?) :: JBool -> (HJScript t1, HJScript t2) -> HJScript () | | | (<|>) :: a -> a -> (a, a) | | | this :: IsClass c => Exp c | | | callMethod :: (IsDeref d, Args e t1) => String -> e -> d -> Exp t2 | | | callVoidMethod :: (Args e t1, IsDeref a) => String -> e -> a -> HJScript () | | | callProc :: Args e t => Exp (t -> t1) -> e -> HJScript () | | | function :: (FormalParams a t, VarsToExps a e) => (e -> HJScript (Exp r)) -> HJScript (Exp (t -> r)) | | | procedure :: (FormalParams a t, VarsToExps a e) => (e -> HJScript ()) -> HJScript (Exp (t -> ())) | | | functionDecl :: (FormalParams a t, VarsToExps a e) => String -> (e -> HJScript (Exp r)) -> HJScript () | | | procedureDecl :: (FormalParams a t, VarsToExps a e) => String -> (e -> HJScript ()) -> HJScript () | | | for :: JInt -> JInt -> (JInt -> HJScript t) -> HJScript () | | | while :: JBool -> HJScript t -> HJScript () | | | doWhile :: HJScript t -> JBool -> HJScript () | | | doIf :: JBool -> HJScript t -> HJScript (Elses ()) -> HJScript () | | | doElse :: HJScript () -> HJScript (Elses ()) | | | doIfElse :: JBool -> (HJScript t1, HJScript t2) -> HJScript () | | | doIfNoElse :: Exp Bool -> HJScript () -> HJScript () | | | noElse :: HJScript (Elses ()) | | | var :: HJScript (Var t) | | | varWith :: Exp t -> HJScript (Var t) | | | inVar :: Exp t -> HJScript (Exp t) | | | new :: (HasConstructor o e t, Args e t) => o -> e -> HJScript (Exp o) | | | (#) :: a -> (a -> b) -> b | | | (#.) :: (a -> b) -> (b -> c) -> a -> c | | | rec :: Exp a -> Exp b -> Exp (Rec a b) | | | first :: Exp (Rec a b) -> Exp a | | | second :: Exp (Rec a b) -> Exp b | | | x :: Exp (Rec a b) -> Exp a | | | y :: Exp (Rec a b) -> Exp b | | | (#!) :: JArray t -> JInt -> Var t | | | jnull :: IsNullable t => Exp t | | | jShow :: JShow t => Exp t -> JString | | | castObject :: (IsClass c1, IsClass c2) => JObject c1 -> JObject c2 | | | hasFeature :: (IsFeature f, IsClass c) => JObject c -> f -> JBool | | | break :: HJScript () | | | continue :: HJScript () | | | true :: JBool | | | ifOp :: JBool -> Exp t -> Exp t -> Exp t | | | false :: JBool | | | int :: Int -> JInt | | | float :: Float -> JFloat | | | bool :: Bool -> JBool | | | string :: String -> JString | | | type HJScript = XMLGenT HJScript' | | | class IsHJScript a where | | | | outputBlock :: Block () -> HJScript () | | | outputStmt :: Stmt () -> HJScript () | | | evaluateHJScript :: HJScript (Exp t) -> Block t | | | evalHJScript :: HJScript t -> (t, Block ()) | | | module Language.HJavaScript.Syntax |
|
|
| Documentation |
|
|
| Incrementing or decrementing numbers.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| Assignment
|
|
|
| Plus with
|
|
|
| Alternative if-else syntax: isTrue ? (doA,doB)
|
|
| (<|>) :: a -> a -> (a, a) | Source |
|
| Providing a way of writing if-else expression as in: isTrue ? doA | doB
|
|
|
|
|
|
|
|
|
|
|
| Anonymous function, returning an expression
|
|
|
| Anonymous void function.
|
|
|
| Function declaration
|
|
|
| Procedure declaration.
|
|
|
| for
|
|
|
| while
|
|
|
| doWhile
|
|
|
| doIf
|
|
|
| doElse
|
|
|
| doIfElse
|
|
|
| Only an if branch
|
|
|
| No else branch.
|
|
|
|
|
|
|
|
|
|
| (#) :: a -> (a -> b) -> b | Source |
|
| Dereferencing operator, similar to the dot operator in JavaScript.
E.g. document.forms => document # forms, same as forms document
|
|
| (#.) :: (a -> b) -> (b -> c) -> a -> c | Source |
|
|
|
|
|
|
|
|
|
|
|
|
|
| Accessing arrays.
|
|
|
| Null value
|
|
|
| Converts to JString expression.
|
|
|
| Casting an JObject
|
|
|
| Checks if an object is supported by browser
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| class IsHJScript a where | Source |
|
| IsHJscript class with function toHJScript for converting
instances to HJScript ()
| | | Methods | | | Instances | |
|
|
|
| Adds a block
|
|
|
| Adds a statement
|
|
|
|
|
| Evaluate a script returning a tuple of the produced value and
a block of code.
|
|
| module Language.HJavaScript.Syntax |
|
| Produced by Haddock version 2.4.2 |