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 |
Domain and Purpose
GHC.JS.Syntax defines the Syntax for the JS backend in GHC. It comports with the ECMA-262 although not every production rule of the standard is represented. Code in this module is a fork of JMacro (BSD 3 Clause) by Gershom Bazerman, heavily modified to accomodate GHC's constraints.
Strategy
Nothing fancy in this module, this is a classic deeply embeded AST for JS. We define numerous ADTs and pattern synonyms to make pattern matching and constructing ASTs easier.
Consumers
The entire JS backend consumes this module, e.g., the modules in GHC.StgToJS.*. Please see
Make
for a module which provides helper functions that use the deeply embedded DSL defined in this module to provide some of the benefits of a shallow embedding.
Synopsis
- data JStat
- = DeclStat !Ident !(Maybe JExpr)
- | ReturnStat JExpr
- | IfStat JExpr JStat JStat
- | WhileStat Bool JExpr JStat
- | ForInStat Bool Ident JExpr JStat
- | SwitchStat JExpr [(JExpr, JStat)] JStat
- | TryStat JStat Ident JStat JStat
- | BlockStat [JStat]
- | ApplStat JExpr [JExpr]
- | UOpStat JUOp JExpr
- | AssignStat JExpr JExpr
- | UnsatBlock (IdentSupply JStat)
- | LabelStat JsLabel JStat
- | BreakStat (Maybe JsLabel)
- | ContinueStat (Maybe JsLabel)
- data JExpr
- data JVal
- = JVar Ident
- | JList [JExpr]
- | JDouble SaneDouble
- | JInt Integer
- | JStr FastString
- | JRegEx FastString
- | JHash (UniqMap FastString JExpr)
- | JFunc [Ident] JStat
- | UnsatVal (IdentSupply JVal)
- data JOp
- = EqOp
- | StrictEqOp
- | NeqOp
- | StrictNeqOp
- | GtOp
- | GeOp
- | LtOp
- | LeOp
- | AddOp
- | SubOp
- | MulOp
- | DivOp
- | ModOp
- | LeftShiftOp
- | RightShiftOp
- | ZRightShiftOp
- | BAndOp
- | BOrOp
- | BXorOp
- | LAndOp
- | LOrOp
- | InstanceofOp
- | InOp
- data JUOp
- newtype Ident = TxtI {
- itxt :: FastString
- identFS :: Ident -> FastString
- type JsLabel = LexicalFastString
- pattern New :: JExpr -> JExpr
- pattern Not :: JExpr -> JExpr
- pattern Negate :: JExpr -> JExpr
- pattern Add :: JExpr -> JExpr -> JExpr
- pattern Sub :: JExpr -> JExpr -> JExpr
- pattern Mul :: JExpr -> JExpr -> JExpr
- pattern Div :: JExpr -> JExpr -> JExpr
- pattern Mod :: JExpr -> JExpr -> JExpr
- pattern BOr :: JExpr -> JExpr -> JExpr
- pattern BAnd :: JExpr -> JExpr -> JExpr
- pattern BXor :: JExpr -> JExpr -> JExpr
- pattern BNot :: JExpr -> JExpr
- pattern LOr :: JExpr -> JExpr -> JExpr
- pattern LAnd :: JExpr -> JExpr -> JExpr
- pattern Int :: Integer -> JExpr
- pattern String :: FastString -> JExpr
- pattern PreInc :: JExpr -> JExpr
- pattern PostInc :: JExpr -> JExpr
- pattern PreDec :: JExpr -> JExpr
- pattern PostDec :: JExpr -> JExpr
- newtype IdentSupply a = IS {
- runIdentSupply :: State [Ident] a
- newIdentSupply :: Maybe FastString -> [Ident]
- pseudoSaturate :: IdentSupply a -> a
- newtype SaneDouble = SaneDouble {}
Deeply embedded JS datatypes
JavaScript statements, see the ECMA262 Reference for details
DeclStat !Ident !(Maybe JExpr) | Variable declarations: var foo [= e] |
ReturnStat JExpr | Return |
IfStat JExpr JStat JStat | If |
WhileStat Bool JExpr JStat | While, bool is "do" when True |
ForInStat Bool Ident JExpr JStat | For-in, bool is "each' when True |
SwitchStat JExpr [(JExpr, JStat)] JStat | Switch |
TryStat JStat Ident JStat JStat | Try |
BlockStat [JStat] | Blocks |
ApplStat JExpr [JExpr] | Application |
UOpStat JUOp JExpr | Unary operators |
AssignStat JExpr JExpr | Binding form: |
UnsatBlock (IdentSupply JStat) | Unsaturated blocks see |
LabelStat JsLabel JStat | Statement Labels, makes me nostalgic for qbasic |
BreakStat (Maybe JsLabel) | Break |
ContinueStat (Maybe JsLabel) | Continue |
Instances
JavaScript Expressions
ValExpr JVal | All values are trivially expressions |
SelExpr JExpr Ident | Selection: Obj.foo, see |
IdxExpr JExpr JExpr | Indexing: Obj[foo], see |
InfixExpr JOp JExpr JExpr | Infix Expressions, see |
UOpExpr JUOp JExpr | Unary Expressions |
IfExpr JExpr JExpr JExpr | If-expression |
ApplExpr JExpr [JExpr] | Application |
UnsatExpr (IdentSupply JExpr) | An Unsaturated expression.
See |
Instances
JavaScript values
JVar Ident | A variable reference |
JList [JExpr] | A JavaScript list, or what JS calls an Array |
JDouble SaneDouble | A Double |
JInt Integer | A BigInt |
JStr FastString | A String |
JRegEx FastString | A Regex |
JHash (UniqMap FastString JExpr) | A JS HashMap: |
JFunc [Ident] JStat | A function |
UnsatVal (IdentSupply JVal) | An Unsaturated value, see |
Instances
JS Binary Operators. We do not deeply embed the comma operator and the assignment operators
EqOp | Equality: |
StrictEqOp | Strict Equality: |
NeqOp | InEquality: |
StrictNeqOp | Strict InEquality |
GtOp | Greater Than: |
GeOp | Greater Than or Equal: |
LtOp | Less Than: < |
LeOp | Less Than or Equal: <= |
AddOp | Addition: + |
SubOp | Subtraction: - |
MulOp | Multiplication * |
DivOp | Division: / |
ModOp | Remainder: % |
LeftShiftOp | Left Shift: << |
RightShiftOp | Right Shift: >> |
ZRightShiftOp | Unsigned RightShift: >>> |
BAndOp | Bitwise And: & |
BOrOp | Bitwise Or: | |
BXorOp | Bitwise XOr: ^ |
LAndOp | Logical And: && |
LOrOp | Logical Or: || |
InstanceofOp | instanceof |
InOp | in |
Instances
Data JOp Source # | |
Defined in GHC.JS.Syntax gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> JOp -> c JOp Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c JOp Source # toConstr :: JOp -> Constr Source # dataTypeOf :: JOp -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c JOp) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c JOp) Source # gmapT :: (forall b. Data b => b -> b) -> JOp -> JOp Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> JOp -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> JOp -> r Source # gmapQ :: (forall d. Data d => d -> u) -> JOp -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> JOp -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> JOp -> m JOp Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> JOp -> m JOp Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> JOp -> m JOp Source # | |
Enum JOp Source # | |
Defined in GHC.JS.Syntax | |
Generic JOp Source # | |
Show JOp Source # | |
NFData JOp Source # | |
Defined in GHC.JS.Syntax | |
Binary JOp Source # | |
Eq JOp Source # | |
Ord JOp Source # | |
type Rep JOp Source # | |
Defined in GHC.JS.Syntax type Rep JOp = D1 ('MetaData "JOp" "GHC.JS.Syntax" "ghc" 'False) ((((C1 ('MetaCons "EqOp" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "StrictEqOp" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "NeqOp" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "StrictNeqOp" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "GtOp" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "GeOp" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "LtOp" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LeOp" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "AddOp" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "SubOp" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MulOp" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "DivOp" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ModOp" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LeftShiftOp" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "RightShiftOp" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ZRightShiftOp" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "BAndOp" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "BOrOp" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "BXorOp" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LAndOp" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "LOrOp" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "InstanceofOp" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "InOp" 'PrefixI 'False) (U1 :: Type -> Type)))))) |
JS Unary Operators
NotOp | Logical Not: |
BNotOp | Bitwise Not: |
NegOp | Negation: |
PlusOp | Unary Plus: |
NewOp | new x |
TypeofOp | typeof x |
DeleteOp | delete x |
YieldOp | yield x |
VoidOp | void x |
PreIncOp | Prefix Increment: |
PostIncOp | Postfix Increment: |
PreDecOp | Prefix Decrement: |
PostDecOp | Postfix Decrement: |
Instances
Data JUOp Source # | |
Defined in GHC.JS.Syntax gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> JUOp -> c JUOp Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c JUOp Source # toConstr :: JUOp -> Constr Source # dataTypeOf :: JUOp -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c JUOp) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c JUOp) Source # gmapT :: (forall b. Data b => b -> b) -> JUOp -> JUOp Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> JUOp -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> JUOp -> r Source # gmapQ :: (forall d. Data d => d -> u) -> JUOp -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> JUOp -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> JUOp -> m JUOp Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> JUOp -> m JUOp Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> JUOp -> m JUOp Source # | |
Enum JUOp Source # | |
Generic JUOp Source # | |
Show JUOp Source # | |
NFData JUOp Source # | |
Defined in GHC.JS.Syntax | |
Binary JUOp Source # | |
Eq JUOp Source # | |
Ord JUOp Source # | |
type Rep JUOp Source # | |
Defined in GHC.JS.Syntax type Rep JUOp = D1 ('MetaData "JUOp" "GHC.JS.Syntax" "ghc" 'False) (((C1 ('MetaCons "NotOp" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "BNotOp" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NegOp" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "PlusOp" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "NewOp" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TypeofOp" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "DeleteOp" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "YieldOp" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "VoidOp" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "PreIncOp" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PostIncOp" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "PreDecOp" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PostDecOp" 'PrefixI 'False) (U1 :: Type -> Type))))) |
A newtype wrapper around FastString
for JS identifiers.
TxtI | |
|
identFS :: Ident -> FastString Source #
type JsLabel = LexicalFastString Source #
A Label used for JStat
, specifically BreakStat
, ContinueStat
and of
course LabelStat
pattern synonyms over JS operators
pattern String :: FastString -> JExpr Source #
pattern synonym to create string values
Ident supply
newtype IdentSupply a Source #
A supply of identifiers, possibly empty
IS | |
|
Instances
Functor IdentSupply Source # | |
Defined in GHC.JS.Syntax fmap :: (a -> b) -> IdentSupply a -> IdentSupply b Source # (<$) :: a -> IdentSupply b -> IdentSupply a Source # | |
Show a => Show (IdentSupply a) Source # | |
Defined in GHC.JS.Syntax | |
NFData (IdentSupply a) Source # | |
Defined in GHC.JS.Syntax rnf :: IdentSupply a -> () Source # | |
Eq a => Eq (IdentSupply a) Source # | |
Defined in GHC.JS.Syntax (==) :: IdentSupply a -> IdentSupply a -> Bool # (/=) :: IdentSupply a -> IdentSupply a -> Bool # | |
Ord a => Ord (IdentSupply a) Source # | |
Defined in GHC.JS.Syntax compare :: IdentSupply a -> IdentSupply a -> Ordering # (<) :: IdentSupply a -> IdentSupply a -> Bool # (<=) :: IdentSupply a -> IdentSupply a -> Bool # (>) :: IdentSupply a -> IdentSupply a -> Bool # (>=) :: IdentSupply a -> IdentSupply a -> Bool # max :: IdentSupply a -> IdentSupply a -> IdentSupply a # min :: IdentSupply a -> IdentSupply a -> IdentSupply a # |
newIdentSupply :: Maybe FastString -> [Ident] Source #
pseudoSaturate :: IdentSupply a -> a Source #
Given a Pseudo-saturate a value with garbage identifiers.
Utility
newtype SaneDouble Source #
A newtype wrapper around Double
to ensure we never generate a Double
that becomes a NaN
, see 'Eq SaneDouble', 'Ord SaneDouble' for details on
Sane-ness