Stability | experimental |
---|---|
Maintainer | Joel Bjornson joel.bjornson@gmail.com Niklas Broberg nibro@cs.chalmers.se |
Language.HJavaScript.Syntax
Contents
- Primitive type classes.
- Fundamental data types.
- Data types and classes for object representation.
- Misc
- Types for functions and parameters.
- Array representation.
- Type synonyms.
- Type classes for expression representation.
- Helper functions
- Render function producing multi-line pretty-printed JavaScript code.
Description
- class JType t
- data Exp t where
- JInt :: Int -> Exp Int
- JFloat :: Float -> Exp Float
- JBool :: Bool -> Exp Bool
- JString :: String -> Exp String
- JRec :: Exp a -> Exp b -> Exp (Rec a b)
- JFst :: Exp (Rec a b) -> Exp a
- JSnd :: Exp (Rec a b) -> Exp b
- JConst :: String -> Exp t
- JAssign :: Var t -> Exp t -> Exp t
- JAssignWith :: Var t -> AssignOp t -> Exp t -> Exp t
- JNeg :: Exp t -> Exp t
- JNot :: Exp Bool -> Exp Bool
- JBinOp :: Exp t -> BinOp t r -> Exp t -> Exp r
- JIncrement :: Num t => PostPre -> Var t -> Exp t
- JDecrement :: Num t => PostPre -> Var t -> Exp t
- JIfOp :: Exp Bool -> Exp t -> Exp t -> Exp t
- JCall :: Args e t => Exp (t -> r) -> e -> Exp r
- JNew :: (Args e t, HasConstructor c e t) => c -> e -> Exp c
- JDelete :: Var a -> Exp Bool
- JDeref :: IsDeref d => d -> String -> Exp t
- JFunction :: FormalParams a t => Maybe String -> a -> Block r -> Exp (t -> r)
- JThis :: IsClass c => Exp c
- JBlock :: Block () -> Exp ()
- JNull :: IsNullable t => Exp t
- JCastObject :: (IsClass c1, IsClass c2) => Exp c1 -> Exp c2
- JValueOf :: Var t -> Exp t
- JIsImpl :: (IsClass c, IsFeature f) => Exp c -> f -> Exp Bool
- JShow :: JShow t => Exp t -> Exp String
- data Rec a b
- data Var t where
- data Stmt t where
- VarDecl :: String -> Stmt ()
- VarDeclAssign :: String -> Exp t -> Stmt ()
- VarAssign :: String -> Exp t -> Stmt ()
- ExpStmt :: Exp t -> Stmt ()
- While :: Exp Bool -> Block () -> Stmt ()
- DoWhile :: Block () -> Exp Bool -> Stmt ()
- For :: Stmt t1 -> Exp Bool -> Exp t2 -> Block () -> Stmt ()
- ForIn :: IsDeref d => Var String -> d -> Block () -> Stmt ()
- Break :: Stmt ()
- Continue :: Stmt ()
- Return :: Exp t -> Stmt t
- If :: Exp Bool -> Block t -> Elses t -> Stmt ()
- data Block t where
- class Show c => IsClass c
- class (IsClass c, Args e t) => HasConstructor c e t
- class Show r => IsDeref r
- data AssignOp t where
- data BinOp t r where
- Plus :: PlusOpType t => BinOp t t
- Minus :: Num t => BinOp t t
- Times :: Num t => BinOp t t
- Div :: Num t => BinOp t t
- Mod :: BinOp Int Int
- And :: BinOp Bool Bool
- Or :: BinOp Bool Bool
- Equals :: BinOp t Bool
- NotEquals :: BinOp t Bool
- GThan :: Num t => BinOp t Bool
- LThan :: Num t => BinOp t Bool
- GEThan :: Num t => BinOp t Bool
- LEThan :: Num t => BinOp t Bool
- class PlusOpType a
- data PostPre
- data Elses t where
- class IsNullable a
- class Show a => IsFeature a
- class JShow a where
- class Show e => Args e t | e -> t
- class ParamType t
- class (Show a, ParamType t) => FormalParams a t | a -> t where
- mkFParams :: forall b. (a -> b) -> Int -> a
- showsFParams :: a -> ShowS
- class VarsToExps v e | v -> e, e -> v where
- v2e :: v -> e
- data Array t = Array
- type JInt = Exp Int
- type JString = Exp String
- type JBool = Exp Bool
- type JFloat = Exp Float
- type JVoid = Exp ()
- type JObject c = Exp c
- type JArray t = Exp (Array t)
- class IsExp e t | e -> t where
- class IsExp e String => IsJString e where
- class IsExp e Bool => IsJBool e where
- class IsExp e Int => IsJInt e where
- class IsExp e Float => IsJFloat e where
- val :: Var t -> Exp t
- toBlock :: Stmt t -> Block t
- deref :: IsDeref d => String -> d -> Exp t
- derefVar :: IsDeref d => String -> d -> Var a
- propertyVar :: (IsDeref d, JShow p) => Exp p -> d -> Var a
- call :: Args e t => Exp (t -> r) -> e -> Exp r
- methodCall :: (Args e t1, IsDeref d) => String -> e -> d -> Exp t2
- voidMethodCall :: (Args e t1, IsDeref a) => String -> e -> a -> Stmt ()
- methodCallNoArgs :: IsDeref d => String -> d -> Exp t
- voidMethodCallNoArgs :: IsDeref d => String -> d -> Stmt ()
- renderBlock :: Block r -> String
Primitive type classes.
JavaScript types
Fundamental data types.
Constructors
Instances
Show (Exp t) | Show for Exp |
IsClass c => IsDeref (Exp c) | |
JShow a => JShow (Exp a) | |
IsExp (Exp t) t | |
Args (Exp t) t | |
VarsToExps (Var t) (Exp t) | |
VarsToExps (Var t1, Var t2) (Exp t1, Exp t2) | |
Args (Exp t1, Exp t2) (t1, t2) | |
VarsToExps (Var t1, Var t2, Var t3) (Exp t1, Exp t2, Exp t3) | |
Args (Exp t1, Exp t2, Exp t3) (t1, t2, t3) | |
VarsToExps (Var t1, Var t2, Var t3, Var t4) (Exp t1, Exp t2, Exp t3, Exp t4) | |
Args (Exp t1, Exp t2, Exp t3, Exp t4) (t1, t2, t3, t4) | |
VarsToExps (Var t1, Var t2, Var t3, Var t4, Var t5) (Exp t1, Exp t2, Exp t3, Exp t4, Exp t5) | |
Args (Exp t1, Exp t2, Exp t3, Exp t4, Exp t5) (t1, t2, t3, t4, t5) |
Constructors
JVar :: String -> Var a | |
JParam :: String -> Var a | |
JMember :: String -> Var a | |
JDerefVar :: IsDeref d => d -> String -> Var a | |
JArrayIndex :: Exp (Array t) -> Exp Int -> Var t | |
JPropertyVar :: (IsDeref d, JShow p) => d -> Exp p -> Var a |
Instances
Show (Var t) | |
ParamType t => FormalParams (Var t) t | |
VarsToExps (Var t) (Exp t) | |
VarsToExps (Var t1, Var t2) (Exp t1, Exp t2) | |
ParamType (t1, t2) => FormalParams (Var t1, Var t2) (t1, t2) | |
VarsToExps (Var t1, Var t2, Var t3) (Exp t1, Exp t2, Exp t3) | |
ParamType (t1, t2, t3) => FormalParams (Var t1, Var t2, Var t3) (t1, t2, t3) | |
VarsToExps (Var t1, Var t2, Var t3, Var t4) (Exp t1, Exp t2, Exp t3, Exp t4) | |
ParamType (t1, t2, t3, t4) => FormalParams (Var t1, Var t2, Var t3, Var t4) (t1, t2, t3, t4) | |
VarsToExps (Var t1, Var t2, Var t3, Var t4, Var t5) (Exp t1, Exp t2, Exp t3, Exp t4, Exp t5) | |
ParamType (t1, t2, t3, t4, t5) => FormalParams (Var t1, Var t2, Var t3, Var t4, Var t5) (t1, t2, t3, t4, t5) |
Constructors
VarDecl :: String -> Stmt () | |
VarDeclAssign :: String -> Exp t -> Stmt () | |
VarAssign :: String -> Exp t -> Stmt () | |
ExpStmt :: Exp t -> Stmt () | |
While :: Exp Bool -> Block () -> Stmt () | |
DoWhile :: Block () -> Exp Bool -> Stmt () | |
For :: Stmt t1 -> Exp Bool -> Exp t2 -> Block () -> Stmt () | |
ForIn :: IsDeref d => Var String -> d -> Block () -> Stmt () | |
Break :: Stmt () | |
Continue :: Stmt () | |
Return :: Exp t -> Stmt t | |
If :: Exp Bool -> Block t -> Elses t -> Stmt () |
Data types and classes for object representation.
class (IsClass c, Args e t) => HasConstructor c e t Source
Class for binding objects with constructors. E.g. o = new Date();
class Show r => IsDeref r Source
Class for derefable data types, used to allow the creation of dereferencing objects. Examples: Math.random() or document.write()
Misc
Assign Operator
Binary Operator
Constructors
Plus :: PlusOpType t => BinOp t t | |
Minus :: Num t => BinOp t t | |
Times :: Num t => BinOp t t | |
Div :: Num t => BinOp t t | |
Mod :: BinOp Int Int | |
And :: BinOp Bool Bool | |
Or :: BinOp Bool Bool | |
Equals :: BinOp t Bool | |
NotEquals :: BinOp t Bool | |
GThan :: Num t => BinOp t Bool | |
LThan :: Num t => BinOp t Bool | |
GEThan :: Num t => BinOp t Bool | |
LEThan :: Num t => BinOp t Bool |
class PlusOpType a Source
Instances
class IsNullable a Source
Allows values to be compared to JNull. E.g. for checking that an object is instantiated or is accessible.
Instances
IsNullable String | All JString values along with all objects and all functions can be null. |
IsClass c => IsNullable c | |
IsNullable (t -> r) |
Class that represents showable types
Types for functions and parameters.
class Show e => Args e t | e -> tSource
Args represents types that can be passed as arguments to JavaScript functions.
Class for parameter types to JavaScript functions
Instances
ParamType () | Instanses for tuples,triples etc.. |
JType t => ParamType t | |
(JType t1, JType t2) => ParamType (t1, t2) | |
(JType t1, JType t2, JType t3) => ParamType (t1, t2, t3) | |
(JType t1, JType t2, JType t3, JType t4) => ParamType (t1, t2, t3, t4) | |
(JType t1, JType t2, JType t3, JType t4, JType t5) => ParamType (t1, t2, t3, t4, t5) |
class (Show a, ParamType t) => FormalParams a t | a -> t whereSource
JFormal params represents parameters passed to a function along with their corresponding types.
Instances
FormalParams () () | |
ParamType t => FormalParams (Var t) t | |
ParamType (t1, t2) => FormalParams (Var t1, Var t2) (t1, t2) | |
ParamType (t1, t2, t3) => FormalParams (Var t1, Var t2, Var t3) (t1, t2, t3) | |
ParamType (t1, t2, t3, t4) => FormalParams (Var t1, Var t2, Var t3, Var t4) (t1, t2, t3, t4) | |
ParamType (t1, t2, t3, t4, t5) => FormalParams (Var t1, Var t2, Var t3, Var t4, Var t5) (t1, t2, t3, t4, t5) |
class VarsToExps v e | v -> e, e -> v whereSource
Instances
VarsToExps () () | |
VarsToExps (Var t) (Exp t) | |
VarsToExps (Var t1, Var t2) (Exp t1, Exp t2) | |
VarsToExps (Var t1, Var t2, Var t3) (Exp t1, Exp t2, Exp t3) | |
VarsToExps (Var t1, Var t2, Var t3, Var t4) (Exp t1, Exp t2, Exp t3, Exp t4) | |
VarsToExps (Var t1, Var t2, Var t3, Var t4, Var t5) (Exp t1, Exp t2, Exp t3, Exp t4, Exp t5) |
Array representation.
Type synonyms.
Type classes for expression representation.
class IsExp e t | e -> t whereSource
Class for representing expressions. First parameter is the expression, second a TBool for variable or constant. Third parameter represents the type.
Helper functions
methodCallNoArgs :: IsDeref d => String -> d -> Exp tSource
Render function producing multi-line pretty-printed JavaScript code.
renderBlock :: Block r -> StringSource