Safe Haskell | None |
---|---|
Language | Haskell2010 |
Cubix.Language.JavaScript.Parametric.Common
Synopsis
- data IdentIsJSExpression (e :: Type -> Type) i = i ~ JSExpressionL => IdentIsJSExpression (e IdentL)
- data JSExpressionIsLocalVarInit (e :: Type -> Type) i = i ~ LocalVarInitL => JSExpressionIsLocalVarInit (e JSExpressionL)
- data JSExpressionIsVarDeclBinder (e :: Type -> Type) i = i ~ VarDeclBinderL => JSExpressionIsVarDeclBinder (e JSExpressionL)
- data MultiLocalVarDeclIsJSStatement (e :: Type -> Type) i = i ~ JSStatementL => MultiLocalVarDeclIsJSStatement (e MultiLocalVarDeclL)
- data JSExpressionIsRhs (e :: Type -> Type) i = i ~ RhsL => JSExpressionIsRhs (e JSExpressionL)
- data JSExpressionIsLhs (e :: Type -> Type) i = i ~ LhsL => JSExpressionIsLhs (e JSExpressionL)
- data JSAssignOpIsAssignOp (e :: Type -> Type) i = i ~ AssignOpL => JSAssignOpIsAssignOp (e JSAssignOpL)
- data AssignIsJSExpression (e :: Type -> Type) i = i ~ JSExpressionL => AssignIsJSExpression (e AssignL)
- data BlockIsJSStatement (e :: Type -> Type) i = i ~ JSStatementL => BlockIsJSStatement (e BlockL)
- data JSStatementIsBlockItem (e :: Type -> Type) i = i ~ BlockItemL => JSStatementIsBlockItem (e JSStatementL)
- data JSBlockIsJSAST (e :: Type -> Type) i = i ~ JSASTL => JSBlockIsJSAST (e JSBlockL)
- iJSBlockIsJSAST :: forall h fs a j. ((:-<:) JSBlockIsJSAST fs, InjF fs JSASTL j) => CxtS h fs a JSBlockL -> CxtS h fs a j
- iJSStatementIsBlockItem :: forall h fs a j. ((:-<:) JSStatementIsBlockItem fs, InjF fs BlockItemL j) => CxtS h fs a JSStatementL -> CxtS h fs a j
- iBlockIsJSStatement :: forall h fs a j. ((:-<:) BlockIsJSStatement fs, InjF fs JSStatementL j) => CxtS h fs a BlockL -> CxtS h fs a j
- iAssignIsJSExpression :: forall h fs a j. ((:-<:) AssignIsJSExpression fs, InjF fs JSExpressionL j) => CxtS h fs a AssignL -> CxtS h fs a j
- iJSAssignOpIsAssignOp :: forall h fs a j. ((:-<:) JSAssignOpIsAssignOp fs, InjF fs AssignOpL j) => CxtS h fs a JSAssignOpL -> CxtS h fs a j
- iJSExpressionIsLhs :: forall h fs a j. ((:-<:) JSExpressionIsLhs fs, InjF fs LhsL j) => CxtS h fs a JSExpressionL -> CxtS h fs a j
- iJSExpressionIsRhs :: forall h fs a j. ((:-<:) JSExpressionIsRhs fs, InjF fs RhsL j) => CxtS h fs a JSExpressionL -> CxtS h fs a j
- iMultiLocalVarDeclIsJSStatement :: forall h fs a j. ((:-<:) MultiLocalVarDeclIsJSStatement fs, InjF fs JSStatementL j) => CxtS h fs a MultiLocalVarDeclL -> CxtS h fs a j
- iJSExpressionIsVarDeclBinder :: forall h fs a j. ((:-<:) JSExpressionIsVarDeclBinder fs, InjF fs VarDeclBinderL j) => CxtS h fs a JSExpressionL -> CxtS h fs a j
- iJSExpressionIsLocalVarInit :: forall h fs a j. ((:-<:) JSExpressionIsLocalVarInit fs, InjF fs LocalVarInitL j) => CxtS h fs a JSExpressionL -> CxtS h fs a j
- iIdentIsJSExpression :: forall h fs a j. ((:-<:) IdentIsJSExpression fs, InjF fs JSExpressionL j) => CxtS h fs a IdentL -> CxtS h fs a j
- data MaybeIdentIsJSIdent e l where
- MaybeIdentIsJSIdent :: e (Maybe IdentL) -> MaybeIdentIsJSIdent e JSIdentL
- iMaybeIdentIsJSIdent :: forall h fs a j. ((:-<:) MaybeIdentIsJSIdent fs, InjF fs JSIdentL j) => CxtS h fs a (Maybe IdentL) -> CxtS h fs a j
- pattern JSIdent' :: (MaybeIdentIsJSIdent :-<: fs, Ident :-<: fs, MaybeF :-<: fs, All HFunctor fs) => String -> CxtS h fs a JSIdentL
- data JSFor e l where
- JSFor :: e [JSExpressionL] -> e [JSExpressionL] -> e [JSExpressionL] -> e JSStatementL -> JSFor e JSStatementL
- JSForIn :: e JSExpressionL -> e JSBinOpL -> e JSExpressionL -> e JSStatementL -> JSFor e JSStatementL
- JSForVar :: e [SingleLocalVarDeclL] -> e [JSExpressionL] -> e [JSExpressionL] -> e JSStatementL -> JSFor e JSStatementL
- JSForVarIn :: e SingleLocalVarDeclL -> e JSBinOpL -> e JSExpressionL -> e JSStatementL -> JSFor e JSStatementL
- iJSForVarIn :: forall h fs a j. ((:-<:) JSFor fs, InjF fs JSStatementL j) => CxtS h fs a SingleLocalVarDeclL -> CxtS h fs a JSBinOpL -> CxtS h fs a JSExpressionL -> CxtS h fs a JSStatementL -> CxtS h fs a j
- iJSForVar :: forall h fs a j. ((:-<:) JSFor fs, InjF fs JSStatementL j) => CxtS h fs a [SingleLocalVarDeclL] -> CxtS h fs a [JSExpressionL] -> CxtS h fs a [JSExpressionL] -> CxtS h fs a JSStatementL -> CxtS h fs a j
- iJSForIn :: forall h fs a j. ((:-<:) JSFor fs, InjF fs JSStatementL j) => CxtS h fs a JSExpressionL -> CxtS h fs a JSBinOpL -> CxtS h fs a JSExpressionL -> CxtS h fs a JSStatementL -> CxtS h fs a j
- iJSFor :: forall h fs a j. ((:-<:) JSFor fs, InjF fs JSStatementL j) => CxtS h fs a [JSExpressionL] -> CxtS h fs a [JSExpressionL] -> CxtS h fs a [JSExpressionL] -> CxtS h fs a JSStatementL -> CxtS h fs a j
- data BlockWithPrelude e l where
- BlockWithPrelude :: [String] -> e BlockL -> BlockWithPrelude e JSBlockL
- iBlockWithPrelude :: forall h fs a j. ((:-<:) BlockWithPrelude fs, InjF fs JSBlockL j) => [String] -> CxtS h fs a BlockL -> CxtS h fs a j
- data FunctionCallIsJSExpression (e :: Type -> Type) i = i ~ JSExpressionL => FunctionCallIsJSExpression (e FunctionCallL)
- data JSExpressionIsPositionalArgExp (e :: Type -> Type) i = i ~ PositionalArgExpL => JSExpressionIsPositionalArgExp (e JSExpressionL)
- data JSExpressionIsFunctionExp (e :: Type -> Type) i = i ~ FunctionExpL => JSExpressionIsFunctionExp (e JSExpressionL)
- data FunctionDefIsJSStatement (e :: Type -> Type) i = i ~ JSStatementL => FunctionDefIsJSStatement (e FunctionDefL)
- data JSBlockIsFunctionBody (e :: Type -> Type) i = i ~ FunctionBodyL => JSBlockIsFunctionBody (e JSBlockL)
- iJSBlockIsFunctionBody :: forall h fs a j. ((:-<:) JSBlockIsFunctionBody fs, InjF fs FunctionBodyL j) => CxtS h fs a JSBlockL -> CxtS h fs a j
- iFunctionDefIsJSStatement :: forall h fs a j. ((:-<:) FunctionDefIsJSStatement fs, InjF fs JSStatementL j) => CxtS h fs a FunctionDefL -> CxtS h fs a j
- iJSExpressionIsFunctionExp :: forall h fs a j. ((:-<:) JSExpressionIsFunctionExp fs, InjF fs FunctionExpL j) => CxtS h fs a JSExpressionL -> CxtS h fs a j
- iJSExpressionIsPositionalArgExp :: forall h fs a j. ((:-<:) JSExpressionIsPositionalArgExp fs, InjF fs PositionalArgExpL j) => CxtS h fs a JSExpressionL -> CxtS h fs a j
- iFunctionCallIsJSExpression :: forall h fs a j. ((:-<:) FunctionCallIsJSExpression fs, InjF fs JSExpressionL j) => CxtS h fs a FunctionCallL -> CxtS h fs a j
- type MJSSig = '[JSAST, JSAccessor, JSAnnot, JSArrayElement, JSAssignOp, JSBinOp, JSBlock, JSExpression, JSObjectProperty, JSPropertyName, JSSemi, JSStatement, JSSwitchParts, JSTryCatch, JSTryFinally, JSUnaryOp, TokenPosn, CommentAnnotation, ListF, MaybeF, JSCommaListF, JSCommaTrailingListF, IdentIsJSExpression, JSExpressionIsLocalVarInit, JSExpressionIsVarDeclBinder, MultiLocalVarDeclIsJSStatement, JSExpressionIsRhs, JSExpressionIsLhs, JSAssignOpIsAssignOp, AssignIsJSExpression, BlockIsJSStatement, JSStatementIsBlockItem, BlockWithPrelude, JSBlockIsJSAST, FunctionCallIsJSExpression, JSExpressionIsPositionalArgExp, JSExpressionIsFunctionExp, FunctionDefIsJSStatement, JSBlockIsFunctionBody, MaybeIdentIsJSIdent, JSFor, OptLocalVarInit, SingleLocalVarDecl, Ident, AssignOpEquals, Assign, Block, TupleBinder, EmptyLocalVarDeclAttrs, MultiLocalVarDecl, EmptyBlockEnd, EmptyMultiLocalVarDeclCommonAttrs, FunctionCall, EmptyFunctionCallAttrs, FunctionArgumentList, PositionalArgument, FunctionDef, EmptyFunctionDefAttrs, PositionalParameter, EmptyParameterAttrs]
- type MJSTerm = Term MJSSig
- type MJSTermLab = TermLab MJSSig
- type MJSCxt h a = CxtS h MJSSig a
- type MJSCxtA h a p = AnnCxtS p h MJSSig a
- translate :: JSTerm l -> MJSTerm l
- untranslate :: MJSTerm l -> JSTerm l
- data JSCommaTrailingListF e l where
- JSCTLComma :: e (JSCommaList l) -> e JSAnnotL -> JSCommaTrailingListF e (JSCommaTrailingList l)
- JSCTLNone :: e (JSCommaList l) -> JSCommaTrailingListF e (JSCommaTrailingList l)
- type JSCommaTrailingList l = JSCommaTrailingList l
- data JSCommaListF e l where
- JSLCons :: e (JSCommaList l) -> e JSAnnotL -> e l -> JSCommaListF e (JSCommaList l)
- JSLOne :: e l -> JSCommaListF e (JSCommaList l)
- JSLNil :: JSCommaListF e (JSCommaList t)
- type JSCommaList l = JSCommaList l
- data CommentAnnotationL
- data CommentAnnotation (e :: Type -> Type) i
- = i ~ CommentAnnotationL => CommentA (e TokenPosnL) String
- | i ~ CommentAnnotationL => WhiteSpace (e TokenPosnL) String
- | i ~ CommentAnnotationL => NoComment
- data TokenPosnL
- data TokenPosn (e :: Type -> Type) i = i ~ TokenPosnL => TokenPn !Int !Int !Int
- data JSVarInitializerL
- pattern JSVarInit :: () => i ~ JSVarInitializerL => !(e JSAnnotL) -> !(e JSExpressionL) -> JSVarInitializer e i
- pattern JSVarInitNone :: () => i ~ JSVarInitializerL => JSVarInitializer e i
- data JSUnaryOpL
- data JSUnaryOp (e :: Type -> Type) i
- = i ~ JSUnaryOpL => JSUnaryOpDecr !(e JSAnnotL)
- | i ~ JSUnaryOpL => JSUnaryOpDelete !(e JSAnnotL)
- | i ~ JSUnaryOpL => JSUnaryOpIncr !(e JSAnnotL)
- | i ~ JSUnaryOpL => JSUnaryOpMinus !(e JSAnnotL)
- | i ~ JSUnaryOpL => JSUnaryOpNot !(e JSAnnotL)
- | i ~ JSUnaryOpL => JSUnaryOpPlus !(e JSAnnotL)
- | i ~ JSUnaryOpL => JSUnaryOpTilde !(e JSAnnotL)
- | i ~ JSUnaryOpL => JSUnaryOpTypeof !(e JSAnnotL)
- | i ~ JSUnaryOpL => JSUnaryOpVoid !(e JSAnnotL)
- data JSTryFinallyL
- data JSTryFinally (e :: Type -> Type) i
- = i ~ JSTryFinallyL => JSFinally !(e JSAnnotL) !(e JSBlockL)
- | i ~ JSTryFinallyL => JSNoFinally
- data JSTryCatchL
- data JSTryCatch (e :: Type -> Type) i
- = i ~ JSTryCatchL => JSCatch !(e JSAnnotL) !(e JSAnnotL) !(e JSExpressionL) !(e JSAnnotL) !(e JSBlockL)
- | i ~ JSTryCatchL => JSCatchIf !(e JSAnnotL) !(e JSAnnotL) !(e JSExpressionL) !(e JSAnnotL) !(e JSExpressionL) !(e JSAnnotL) !(e JSBlockL)
- data JSSwitchPartsL
- data JSSwitchParts (e :: Type -> Type) i
- = i ~ JSSwitchPartsL => JSCase !(e JSAnnotL) !(e JSExpressionL) !(e JSAnnotL) !(e [JSStatementL])
- | i ~ JSSwitchPartsL => JSDefault !(e JSAnnotL) !(e JSAnnotL) !(e [JSStatementL])
- data JSStatementL
- data JSStatement (e :: Type -> Type) i
- = i ~ JSStatementL => JSStatementBlock !(e JSAnnotL) !(e [JSStatementL]) !(e JSAnnotL) !(e JSSemiL)
- | i ~ JSStatementL => JSBreak !(e JSAnnotL) !(e JSIdentL) !(e JSSemiL)
- | i ~ JSStatementL => JSConstant !(e JSAnnotL) !(e (JSCommaList JSExpressionL)) !(e JSSemiL)
- | i ~ JSStatementL => JSContinue !(e JSAnnotL) !(e JSIdentL) !(e JSSemiL)
- | i ~ JSStatementL => JSDoWhile !(e JSAnnotL) !(e JSStatementL) !(e JSAnnotL) !(e JSAnnotL) !(e JSExpressionL) !(e JSAnnotL) !(e JSSemiL)
- | i ~ JSStatementL => JSFunction !(e JSAnnotL) !(e JSIdentL) !(e JSAnnotL) !(e (JSCommaList JSIdentL)) !(e JSAnnotL) !(e JSBlockL) !(e JSSemiL)
- | i ~ JSStatementL => JSIf !(e JSAnnotL) !(e JSAnnotL) !(e JSExpressionL) !(e JSAnnotL) !(e JSStatementL)
- | i ~ JSStatementL => JSIfElse !(e JSAnnotL) !(e JSAnnotL) !(e JSExpressionL) !(e JSAnnotL) !(e JSStatementL) !(e JSAnnotL) !(e JSStatementL)
- | i ~ JSStatementL => JSLabelled !(e JSIdentL) !(e JSAnnotL) !(e JSStatementL)
- | i ~ JSStatementL => JSEmptyStatement !(e JSAnnotL)
- | i ~ JSStatementL => JSExpressionStatement !(e JSExpressionL) !(e JSSemiL)
- | i ~ JSStatementL => JSAssignStatement !(e JSExpressionL) !(e JSAssignOpL) !(e JSExpressionL) !(e JSSemiL)
- | i ~ JSStatementL => JSMethodCall !(e JSExpressionL) !(e JSAnnotL) !(e (JSCommaList JSExpressionL)) !(e JSAnnotL) !(e JSSemiL)
- | i ~ JSStatementL => JSReturn !(e JSAnnotL) !(e (Maybe JSExpressionL)) !(e JSSemiL)
- | i ~ JSStatementL => JSSwitch !(e JSAnnotL) !(e JSAnnotL) !(e JSExpressionL) !(e JSAnnotL) !(e JSAnnotL) !(e [JSSwitchPartsL]) !(e JSAnnotL) !(e JSSemiL)
- | i ~ JSStatementL => JSThrow !(e JSAnnotL) !(e JSExpressionL) !(e JSSemiL)
- | i ~ JSStatementL => JSTry !(e JSAnnotL) !(e JSBlockL) !(e [JSTryCatchL]) !(e JSTryFinallyL)
- | i ~ JSStatementL => JSVariable !(e JSAnnotL) !(e (JSCommaList JSExpressionL)) !(e JSSemiL)
- | i ~ JSStatementL => JSWhile !(e JSAnnotL) !(e JSAnnotL) !(e JSExpressionL) !(e JSAnnotL) !(e JSStatementL)
- | i ~ JSStatementL => JSWith !(e JSAnnotL) !(e JSAnnotL) !(e JSExpressionL) !(e JSAnnotL) !(e JSStatementL) !(e JSSemiL)
- data JSSemiL
- data JSSemi (e :: Type -> Type) i
- = i ~ JSSemiL => JSSemi !(e JSAnnotL)
- | i ~ JSSemiL => JSSemiAuto
- data JSPropertyNameL
- data JSPropertyName (e :: Type -> Type) i
- = i ~ JSPropertyNameL => JSPropertyIdent !(e JSAnnotL) !String
- | i ~ JSPropertyNameL => JSPropertyString !(e JSAnnotL) !String
- | i ~ JSPropertyNameL => JSPropertyNumber !(e JSAnnotL) !String
- data JSObjectPropertyL
- data JSObjectProperty (e :: Type -> Type) i
- = i ~ JSObjectPropertyL => JSPropertyAccessor !(e JSAccessorL) !(e JSPropertyNameL) !(e JSAnnotL) !(e [JSExpressionL]) !(e JSAnnotL) !(e JSBlockL)
- | i ~ JSObjectPropertyL => JSPropertyNameandValue !(e JSPropertyNameL) !(e JSAnnotL) !(e [JSExpressionL])
- data JSIdentL
- pattern JSIdentName :: () => i ~ JSIdentL => !(e JSAnnotL) -> !String -> JSIdent e i
- pattern JSIdentNone :: () => i ~ JSIdentL => JSIdent e i
- data JSExpressionL
- data JSExpression (e :: Type -> Type) i
- = i ~ JSExpressionL => JSIdentifier !(e JSAnnotL) !String
- | i ~ JSExpressionL => JSDecimal !(e JSAnnotL) !String
- | i ~ JSExpressionL => JSLiteral !(e JSAnnotL) !String
- | i ~ JSExpressionL => JSHexInteger !(e JSAnnotL) !String
- | i ~ JSExpressionL => JSOctal !(e JSAnnotL) !String
- | i ~ JSExpressionL => JSStringLiteral !(e JSAnnotL) !String
- | i ~ JSExpressionL => JSRegEx !(e JSAnnotL) !String
- | i ~ JSExpressionL => JSArrayLiteral !(e JSAnnotL) !(e [JSArrayElementL]) !(e JSAnnotL)
- | i ~ JSExpressionL => JSAssignExpression !(e JSExpressionL) !(e JSAssignOpL) !(e JSExpressionL)
- | i ~ JSExpressionL => JSCallExpression !(e JSExpressionL) !(e JSAnnotL) !(e (JSCommaList JSExpressionL)) !(e JSAnnotL)
- | i ~ JSExpressionL => JSCallExpressionDot !(e JSExpressionL) !(e JSAnnotL) !(e JSExpressionL)
- | i ~ JSExpressionL => JSCallExpressionSquare !(e JSExpressionL) !(e JSAnnotL) !(e JSExpressionL) !(e JSAnnotL)
- | i ~ JSExpressionL => JSCommaExpression !(e JSExpressionL) !(e JSAnnotL) !(e JSExpressionL)
- | i ~ JSExpressionL => JSExpressionBinary !(e JSExpressionL) !(e JSBinOpL) !(e JSExpressionL)
- | i ~ JSExpressionL => JSExpressionParen !(e JSAnnotL) !(e JSExpressionL) !(e JSAnnotL)
- | i ~ JSExpressionL => JSExpressionPostfix !(e JSExpressionL) !(e JSUnaryOpL)
- | i ~ JSExpressionL => JSExpressionTernary !(e JSExpressionL) !(e JSAnnotL) !(e JSExpressionL) !(e JSAnnotL) !(e JSExpressionL)
- | i ~ JSExpressionL => JSFunctionExpression !(e JSAnnotL) !(e JSIdentL) !(e JSAnnotL) !(e (JSCommaList JSIdentL)) !(e JSAnnotL) !(e JSBlockL)
- | i ~ JSExpressionL => JSMemberDot !(e JSExpressionL) !(e JSAnnotL) !(e JSExpressionL)
- | i ~ JSExpressionL => JSMemberExpression !(e JSExpressionL) !(e JSAnnotL) !(e (JSCommaList JSExpressionL)) !(e JSAnnotL)
- | i ~ JSExpressionL => JSMemberNew !(e JSAnnotL) !(e JSExpressionL) !(e JSAnnotL) !(e (JSCommaList JSExpressionL)) !(e JSAnnotL)
- | i ~ JSExpressionL => JSMemberSquare !(e JSExpressionL) !(e JSAnnotL) !(e JSExpressionL) !(e JSAnnotL)
- | i ~ JSExpressionL => JSNewExpression !(e JSAnnotL) !(e JSExpressionL)
- | i ~ JSExpressionL => JSObjectLiteral !(e JSAnnotL) !(e (JSCommaTrailingList JSObjectPropertyL)) !(e JSAnnotL)
- | i ~ JSExpressionL => JSUnaryExpression !(e JSUnaryOpL) !(e JSExpressionL)
- | i ~ JSExpressionL => JSVarInitExpression !(e JSExpressionL) !(e JSVarInitializerL)
- data JSBlockL
- data JSBlock (e :: Type -> Type) i = i ~ JSBlockL => JSBlock !(e JSAnnotL) !(e [JSStatementL]) !(e JSAnnotL)
- data JSBinOpL
- data JSBinOp (e :: Type -> Type) i
- = i ~ JSBinOpL => JSBinOpAnd !(e JSAnnotL)
- | i ~ JSBinOpL => JSBinOpBitAnd !(e JSAnnotL)
- | i ~ JSBinOpL => JSBinOpBitOr !(e JSAnnotL)
- | i ~ JSBinOpL => JSBinOpBitXor !(e JSAnnotL)
- | i ~ JSBinOpL => JSBinOpDivide !(e JSAnnotL)
- | i ~ JSBinOpL => JSBinOpEq !(e JSAnnotL)
- | i ~ JSBinOpL => JSBinOpGe !(e JSAnnotL)
- | i ~ JSBinOpL => JSBinOpGt !(e JSAnnotL)
- | i ~ JSBinOpL => JSBinOpIn !(e JSAnnotL)
- | i ~ JSBinOpL => JSBinOpInstanceOf !(e JSAnnotL)
- | i ~ JSBinOpL => JSBinOpLe !(e JSAnnotL)
- | i ~ JSBinOpL => JSBinOpLsh !(e JSAnnotL)
- | i ~ JSBinOpL => JSBinOpLt !(e JSAnnotL)
- | i ~ JSBinOpL => JSBinOpMinus !(e JSAnnotL)
- | i ~ JSBinOpL => JSBinOpMod !(e JSAnnotL)
- | i ~ JSBinOpL => JSBinOpNeq !(e JSAnnotL)
- | i ~ JSBinOpL => JSBinOpOr !(e JSAnnotL)
- | i ~ JSBinOpL => JSBinOpPlus !(e JSAnnotL)
- | i ~ JSBinOpL => JSBinOpRsh !(e JSAnnotL)
- | i ~ JSBinOpL => JSBinOpStrictEq !(e JSAnnotL)
- | i ~ JSBinOpL => JSBinOpStrictNeq !(e JSAnnotL)
- | i ~ JSBinOpL => JSBinOpTimes !(e JSAnnotL)
- | i ~ JSBinOpL => JSBinOpUrsh !(e JSAnnotL)
- data JSAssignOpL
- data JSAssignOp (e :: Type -> Type) i
- = i ~ JSAssignOpL => JSAssign !(e JSAnnotL)
- | i ~ JSAssignOpL => JSTimesAssign !(e JSAnnotL)
- | i ~ JSAssignOpL => JSDivideAssign !(e JSAnnotL)
- | i ~ JSAssignOpL => JSModAssign !(e JSAnnotL)
- | i ~ JSAssignOpL => JSPlusAssign !(e JSAnnotL)
- | i ~ JSAssignOpL => JSMinusAssign !(e JSAnnotL)
- | i ~ JSAssignOpL => JSLshAssign !(e JSAnnotL)
- | i ~ JSAssignOpL => JSRshAssign !(e JSAnnotL)
- | i ~ JSAssignOpL => JSUrshAssign !(e JSAnnotL)
- | i ~ JSAssignOpL => JSBwAndAssign !(e JSAnnotL)
- | i ~ JSAssignOpL => JSBwXorAssign !(e JSAnnotL)
- | i ~ JSAssignOpL => JSBwOrAssign !(e JSAnnotL)
- data JSArrayElementL
- data JSArrayElement (e :: Type -> Type) i
- = i ~ JSArrayElementL => JSArrayElement !(e JSExpressionL)
- | i ~ JSArrayElementL => JSArrayComma !(e JSAnnotL)
- data JSAnnotL
- data JSAnnot (e :: Type -> Type) i
- = i ~ JSAnnotL => JSAnnot !(e TokenPosnL) !(e [CommentAnnotationL])
- | i ~ JSAnnotL => JSAnnotSpace
- | i ~ JSAnnotL => JSNoAnnot
- data JSAccessorL
- data JSAccessor (e :: Type -> Type) i
- = i ~ JSAccessorL => JSAccessorGet !(e JSAnnotL)
- | i ~ JSAccessorL => JSAccessorSet !(e JSAnnotL)
- data JSASTL
- data JSAST (e :: Type -> Type) i
- = i ~ JSASTL => JSAstProgram !(e [JSStatementL]) !(e JSAnnotL)
- | i ~ JSASTL => JSAstStatement !(e JSStatementL) !(e JSAnnotL)
- | i ~ JSASTL => JSAstExpression !(e JSExpressionL) !(e JSAnnotL)
- | i ~ JSASTL => JSAstLiteral !(e JSExpressionL) !(e JSAnnotL)
- riJSLCons :: JSCommaListF :<: f => Cxt h f a (JSCommaList l) -> Cxt h f a JSAnnotL -> Cxt h f a l -> Cxt h f a (JSCommaList l)
- riJSLOne :: JSCommaListF :<: f => Cxt h f a l -> Cxt h f a (JSCommaList l)
- riJSLNil :: JSCommaListF :<: f => Cxt h f a (JSCommaList l)
- riJSCTLComma :: JSCommaTrailingListF :<: f => Cxt h f a (JSCommaList l) -> Cxt h f a JSAnnotL -> Cxt h f a (JSCommaTrailingList l)
- riJSCTLNone :: JSCommaTrailingListF :<: f => Cxt h f a (JSCommaList l) -> Cxt h f a (JSCommaTrailingList l)
- type JSTermLab l = TermLab JSSig l
- type JSTerm = Term JSSig
- type JSSig = '[JSAST, JSAccessor, JSAnnot, JSArrayElement, JSAssignOp, JSBinOp, JSBlock, JSExpression, JSIdent, JSObjectProperty, JSPropertyName, JSSemi, JSStatement, JSSwitchParts, JSTryCatch, JSTryFinally, JSUnaryOp, JSVarInitializer, TokenPosn, CommentAnnotation, ListF, MaybeF, JSCommaListF, JSCommaTrailingListF]
- iJSAstProgram :: forall h fs a j. ((:-<:) JSAST fs, InjF fs JSASTL j) => CxtS h fs a [JSStatementL] -> CxtS h fs a JSAnnotL -> CxtS h fs a j
- iJSAstStatement :: forall h fs a j. ((:-<:) JSAST fs, InjF fs JSASTL j) => CxtS h fs a JSStatementL -> CxtS h fs a JSAnnotL -> CxtS h fs a j
- iJSAstExpression :: forall h fs a j. ((:-<:) JSAST fs, InjF fs JSASTL j) => CxtS h fs a JSExpressionL -> CxtS h fs a JSAnnotL -> CxtS h fs a j
- iJSAstLiteral :: forall h fs a j. ((:-<:) JSAST fs, InjF fs JSASTL j) => CxtS h fs a JSExpressionL -> CxtS h fs a JSAnnotL -> CxtS h fs a j
- iJSAccessorGet :: forall h fs a j. ((:-<:) JSAccessor fs, InjF fs JSAccessorL j) => CxtS h fs a JSAnnotL -> CxtS h fs a j
- iJSAccessorSet :: forall h fs a j. ((:-<:) JSAccessor fs, InjF fs JSAccessorL j) => CxtS h fs a JSAnnotL -> CxtS h fs a j
- iJSAnnot :: forall h fs a j. ((:-<:) JSAnnot fs, InjF fs JSAnnotL j) => CxtS h fs a TokenPosnL -> CxtS h fs a [CommentAnnotationL] -> CxtS h fs a j
- iJSAnnotSpace :: forall h fs a j. ((:-<:) JSAnnot fs, InjF fs JSAnnotL j) => CxtS h fs a j
- iJSNoAnnot :: forall h fs a j. ((:-<:) JSAnnot fs, InjF fs JSAnnotL j) => CxtS h fs a j
- iJSArrayElement :: forall h fs a j. ((:-<:) JSArrayElement fs, InjF fs JSArrayElementL j) => CxtS h fs a JSExpressionL -> CxtS h fs a j
- iJSArrayComma :: forall h fs a j. ((:-<:) JSArrayElement fs, InjF fs JSArrayElementL j) => CxtS h fs a JSAnnotL -> CxtS h fs a j
- iJSAssign :: forall h fs a j. ((:-<:) JSAssignOp fs, InjF fs JSAssignOpL j) => CxtS h fs a JSAnnotL -> CxtS h fs a j
- iJSTimesAssign :: forall h fs a j. ((:-<:) JSAssignOp fs, InjF fs JSAssignOpL j) => CxtS h fs a JSAnnotL -> CxtS h fs a j
- iJSDivideAssign :: forall h fs a j. ((:-<:) JSAssignOp fs, InjF fs JSAssignOpL j) => CxtS h fs a JSAnnotL -> CxtS h fs a j
- iJSModAssign :: forall h fs a j. ((:-<:) JSAssignOp fs, InjF fs JSAssignOpL j) => CxtS h fs a JSAnnotL -> CxtS h fs a j
- iJSPlusAssign :: forall h fs a j. ((:-<:) JSAssignOp fs, InjF fs JSAssignOpL j) => CxtS h fs a JSAnnotL -> CxtS h fs a j
- iJSMinusAssign :: forall h fs a j. ((:-<:) JSAssignOp fs, InjF fs JSAssignOpL j) => CxtS h fs a JSAnnotL -> CxtS h fs a j
- iJSLshAssign :: forall h fs a j. ((:-<:) JSAssignOp fs, InjF fs JSAssignOpL j) => CxtS h fs a JSAnnotL -> CxtS h fs a j
- iJSRshAssign :: forall h fs a j. ((:-<:) JSAssignOp fs, InjF fs JSAssignOpL j) => CxtS h fs a JSAnnotL -> CxtS h fs a j
- iJSUrshAssign :: forall h fs a j. ((:-<:) JSAssignOp fs, InjF fs JSAssignOpL j) => CxtS h fs a JSAnnotL -> CxtS h fs a j
- iJSBwAndAssign :: forall h fs a j. ((:-<:) JSAssignOp fs, InjF fs JSAssignOpL j) => CxtS h fs a JSAnnotL -> CxtS h fs a j
- iJSBwXorAssign :: forall h fs a j. ((:-<:) JSAssignOp fs, InjF fs JSAssignOpL j) => CxtS h fs a JSAnnotL -> CxtS h fs a j
- iJSBwOrAssign :: forall h fs a j. ((:-<:) JSAssignOp fs, InjF fs JSAssignOpL j) => CxtS h fs a JSAnnotL -> CxtS h fs a j
- iJSBinOpAnd :: forall h fs a j. ((:-<:) JSBinOp fs, InjF fs JSBinOpL j) => CxtS h fs a JSAnnotL -> CxtS h fs a j
- iJSBinOpBitAnd :: forall h fs a j. ((:-<:) JSBinOp fs, InjF fs JSBinOpL j) => CxtS h fs a JSAnnotL -> CxtS h fs a j
- iJSBinOpBitOr :: forall h fs a j. ((:-<:) JSBinOp fs, InjF fs JSBinOpL j) => CxtS h fs a JSAnnotL -> CxtS h fs a j
- iJSBinOpBitXor :: forall h fs a j. ((:-<:) JSBinOp fs, InjF fs JSBinOpL j) => CxtS h fs a JSAnnotL -> CxtS h fs a j
- iJSBinOpDivide :: forall h fs a j. ((:-<:) JSBinOp fs, InjF fs JSBinOpL j) => CxtS h fs a JSAnnotL -> CxtS h fs a j
- iJSBinOpEq :: forall h fs a j. ((:-<:) JSBinOp fs, InjF fs JSBinOpL j) => CxtS h fs a JSAnnotL -> CxtS h fs a j
- iJSBinOpGe :: forall h fs a j. ((:-<:) JSBinOp fs, InjF fs JSBinOpL j) => CxtS h fs a JSAnnotL -> CxtS h fs a j
- iJSBinOpGt :: forall h fs a j. ((:-<:) JSBinOp fs, InjF fs JSBinOpL j) => CxtS h fs a JSAnnotL -> CxtS h fs a j
- iJSBinOpIn :: forall h fs a j. ((:-<:) JSBinOp fs, InjF fs JSBinOpL j) => CxtS h fs a JSAnnotL -> CxtS h fs a j
- iJSBinOpInstanceOf :: forall h fs a j. ((:-<:) JSBinOp fs, InjF fs JSBinOpL j) => CxtS h fs a JSAnnotL -> CxtS h fs a j
- iJSBinOpLe :: forall h fs a j. ((:-<:) JSBinOp fs, InjF fs JSBinOpL j) => CxtS h fs a JSAnnotL -> CxtS h fs a j
- iJSBinOpLsh :: forall h fs a j. ((:-<:) JSBinOp fs, InjF fs JSBinOpL j) => CxtS h fs a JSAnnotL -> CxtS h fs a j
- iJSBinOpLt :: forall h fs a j. ((:-<:) JSBinOp fs, InjF fs JSBinOpL j) => CxtS h fs a JSAnnotL -> CxtS h fs a j
- iJSBinOpMinus :: forall h fs a j. ((:-<:) JSBinOp fs, InjF fs JSBinOpL j) => CxtS h fs a JSAnnotL -> CxtS h fs a j
- iJSBinOpMod :: forall h fs a j. ((:-<:) JSBinOp fs, InjF fs JSBinOpL j) => CxtS h fs a JSAnnotL -> CxtS h fs a j
- iJSBinOpNeq :: forall h fs a j. ((:-<:) JSBinOp fs, InjF fs JSBinOpL j) => CxtS h fs a JSAnnotL -> CxtS h fs a j
- iJSBinOpOr :: forall h fs a j. ((:-<:) JSBinOp fs, InjF fs JSBinOpL j) => CxtS h fs a JSAnnotL -> CxtS h fs a j
- iJSBinOpPlus :: forall h fs a j. ((:-<:) JSBinOp fs, InjF fs JSBinOpL j) => CxtS h fs a JSAnnotL -> CxtS h fs a j
- iJSBinOpRsh :: forall h fs a j. ((:-<:) JSBinOp fs, InjF fs JSBinOpL j) => CxtS h fs a JSAnnotL -> CxtS h fs a j
- iJSBinOpStrictEq :: forall h fs a j. ((:-<:) JSBinOp fs, InjF fs JSBinOpL j) => CxtS h fs a JSAnnotL -> CxtS h fs a j
- iJSBinOpStrictNeq :: forall h fs a j. ((:-<:) JSBinOp fs, InjF fs JSBinOpL j) => CxtS h fs a JSAnnotL -> CxtS h fs a j
- iJSBinOpTimes :: forall h fs a j. ((:-<:) JSBinOp fs, InjF fs JSBinOpL j) => CxtS h fs a JSAnnotL -> CxtS h fs a j
- iJSBinOpUrsh :: forall h fs a j. ((:-<:) JSBinOp fs, InjF fs JSBinOpL j) => CxtS h fs a JSAnnotL -> CxtS h fs a j
- iJSBlock :: forall h fs a j. ((:-<:) JSBlock fs, InjF fs JSBlockL j) => CxtS h fs a JSAnnotL -> CxtS h fs a [JSStatementL] -> CxtS h fs a JSAnnotL -> CxtS h fs a j
- iJSIdentifier :: forall h fs a j. ((:-<:) JSExpression fs, InjF fs JSExpressionL j) => CxtS h fs a JSAnnotL -> String -> CxtS h fs a j
- iJSDecimal :: forall h fs a j. ((:-<:) JSExpression fs, InjF fs JSExpressionL j) => CxtS h fs a JSAnnotL -> String -> CxtS h fs a j
- iJSLiteral :: forall h fs a j. ((:-<:) JSExpression fs, InjF fs JSExpressionL j) => CxtS h fs a JSAnnotL -> String -> CxtS h fs a j
- iJSHexInteger :: forall h fs a j. ((:-<:) JSExpression fs, InjF fs JSExpressionL j) => CxtS h fs a JSAnnotL -> String -> CxtS h fs a j
- iJSOctal :: forall h fs a j. ((:-<:) JSExpression fs, InjF fs JSExpressionL j) => CxtS h fs a JSAnnotL -> String -> CxtS h fs a j
- iJSStringLiteral :: forall h fs a j. ((:-<:) JSExpression fs, InjF fs JSExpressionL j) => CxtS h fs a JSAnnotL -> String -> CxtS h fs a j
- iJSRegEx :: forall h fs a j. ((:-<:) JSExpression fs, InjF fs JSExpressionL j) => CxtS h fs a JSAnnotL -> String -> CxtS h fs a j
- iJSArrayLiteral :: forall h fs a j. ((:-<:) JSExpression fs, InjF fs JSExpressionL j) => CxtS h fs a JSAnnotL -> CxtS h fs a [JSArrayElementL] -> CxtS h fs a JSAnnotL -> CxtS h fs a j
- iJSAssignExpression :: forall h fs a j. ((:-<:) JSExpression fs, InjF fs JSExpressionL j) => CxtS h fs a JSExpressionL -> CxtS h fs a JSAssignOpL -> CxtS h fs a JSExpressionL -> CxtS h fs a j
- iJSCallExpression :: forall h fs a j. ((:-<:) JSExpression fs, InjF fs JSExpressionL j) => CxtS h fs a JSExpressionL -> CxtS h fs a JSAnnotL -> CxtS h fs a (JSCommaList JSExpressionL) -> CxtS h fs a JSAnnotL -> CxtS h fs a j
- iJSCallExpressionDot :: forall h fs a j. ((:-<:) JSExpression fs, InjF fs JSExpressionL j) => CxtS h fs a JSExpressionL -> CxtS h fs a JSAnnotL -> CxtS h fs a JSExpressionL -> CxtS h fs a j
- iJSCallExpressionSquare :: forall h fs a j. ((:-<:) JSExpression fs, InjF fs JSExpressionL j) => CxtS h fs a JSExpressionL -> CxtS h fs a JSAnnotL -> CxtS h fs a JSExpressionL -> CxtS h fs a JSAnnotL -> CxtS h fs a j
- iJSCommaExpression :: forall h fs a j. ((:-<:) JSExpression fs, InjF fs JSExpressionL j) => CxtS h fs a JSExpressionL -> CxtS h fs a JSAnnotL -> CxtS h fs a JSExpressionL -> CxtS h fs a j
- iJSExpressionBinary :: forall h fs a j. ((:-<:) JSExpression fs, InjF fs JSExpressionL j) => CxtS h fs a JSExpressionL -> CxtS h fs a JSBinOpL -> CxtS h fs a JSExpressionL -> CxtS h fs a j
- iJSExpressionParen :: forall h fs a j. ((:-<:) JSExpression fs, InjF fs JSExpressionL j) => CxtS h fs a JSAnnotL -> CxtS h fs a JSExpressionL -> CxtS h fs a JSAnnotL -> CxtS h fs a j
- iJSExpressionPostfix :: forall h fs a j. ((:-<:) JSExpression fs, InjF fs JSExpressionL j) => CxtS h fs a JSExpressionL -> CxtS h fs a JSUnaryOpL -> CxtS h fs a j
- iJSExpressionTernary :: forall h fs a j. ((:-<:) JSExpression fs, InjF fs JSExpressionL j) => CxtS h fs a JSExpressionL -> CxtS h fs a JSAnnotL -> CxtS h fs a JSExpressionL -> CxtS h fs a JSAnnotL -> CxtS h fs a JSExpressionL -> CxtS h fs a j
- iJSFunctionExpression :: forall h fs a j. ((:-<:) JSExpression fs, InjF fs JSExpressionL j) => CxtS h fs a JSAnnotL -> CxtS h fs a JSIdentL -> CxtS h fs a JSAnnotL -> CxtS h fs a (JSCommaList JSIdentL) -> CxtS h fs a JSAnnotL -> CxtS h fs a JSBlockL -> CxtS h fs a j
- iJSMemberDot :: forall h fs a j. ((:-<:) JSExpression fs, InjF fs JSExpressionL j) => CxtS h fs a JSExpressionL -> CxtS h fs a JSAnnotL -> CxtS h fs a JSExpressionL -> CxtS h fs a j
- iJSMemberExpression :: forall h fs a j. ((:-<:) JSExpression fs, InjF fs JSExpressionL j) => CxtS h fs a JSExpressionL -> CxtS h fs a JSAnnotL -> CxtS h fs a (JSCommaList JSExpressionL) -> CxtS h fs a JSAnnotL -> CxtS h fs a j
- iJSMemberNew :: forall h fs a j. ((:-<:) JSExpression fs, InjF fs JSExpressionL j) => CxtS h fs a JSAnnotL -> CxtS h fs a JSExpressionL -> CxtS h fs a JSAnnotL -> CxtS h fs a (JSCommaList JSExpressionL) -> CxtS h fs a JSAnnotL -> CxtS h fs a j
- iJSMemberSquare :: forall h fs a j. ((:-<:) JSExpression fs, InjF fs JSExpressionL j) => CxtS h fs a JSExpressionL -> CxtS h fs a JSAnnotL -> CxtS h fs a JSExpressionL -> CxtS h fs a JSAnnotL -> CxtS h fs a j
- iJSNewExpression :: forall h fs a j. ((:-<:) JSExpression fs, InjF fs JSExpressionL j) => CxtS h fs a JSAnnotL -> CxtS h fs a JSExpressionL -> CxtS h fs a j
- iJSObjectLiteral :: forall h fs a j. ((:-<:) JSExpression fs, InjF fs JSExpressionL j) => CxtS h fs a JSAnnotL -> CxtS h fs a (JSCommaTrailingList JSObjectPropertyL) -> CxtS h fs a JSAnnotL -> CxtS h fs a j
- iJSUnaryExpression :: forall h fs a j. ((:-<:) JSExpression fs, InjF fs JSExpressionL j) => CxtS h fs a JSUnaryOpL -> CxtS h fs a JSExpressionL -> CxtS h fs a j
- iJSVarInitExpression :: forall h fs a j. ((:-<:) JSExpression fs, InjF fs JSExpressionL j) => CxtS h fs a JSExpressionL -> CxtS h fs a JSVarInitializerL -> CxtS h fs a j
- iJSPropertyAccessor :: forall h fs a j. ((:-<:) JSObjectProperty fs, InjF fs JSObjectPropertyL j) => CxtS h fs a JSAccessorL -> CxtS h fs a JSPropertyNameL -> CxtS h fs a JSAnnotL -> CxtS h fs a [JSExpressionL] -> CxtS h fs a JSAnnotL -> CxtS h fs a JSBlockL -> CxtS h fs a j
- iJSPropertyNameandValue :: forall h fs a j. ((:-<:) JSObjectProperty fs, InjF fs JSObjectPropertyL j) => CxtS h fs a JSPropertyNameL -> CxtS h fs a JSAnnotL -> CxtS h fs a [JSExpressionL] -> CxtS h fs a j
- iJSPropertyIdent :: forall h fs a j. ((:-<:) JSPropertyName fs, InjF fs JSPropertyNameL j) => CxtS h fs a JSAnnotL -> String -> CxtS h fs a j
- iJSPropertyString :: forall h fs a j. ((:-<:) JSPropertyName fs, InjF fs JSPropertyNameL j) => CxtS h fs a JSAnnotL -> String -> CxtS h fs a j
- iJSPropertyNumber :: forall h fs a j. ((:-<:) JSPropertyName fs, InjF fs JSPropertyNameL j) => CxtS h fs a JSAnnotL -> String -> CxtS h fs a j
- iJSSemi :: forall h fs a j. ((:-<:) JSSemi fs, InjF fs JSSemiL j) => CxtS h fs a JSAnnotL -> CxtS h fs a j
- iJSSemiAuto :: forall h fs a j. ((:-<:) JSSemi fs, InjF fs JSSemiL j) => CxtS h fs a j
- iJSStatementBlock :: forall h fs a j. ((:-<:) JSStatement fs, InjF fs JSStatementL j) => CxtS h fs a JSAnnotL -> CxtS h fs a [JSStatementL] -> CxtS h fs a JSAnnotL -> CxtS h fs a JSSemiL -> CxtS h fs a j
- iJSBreak :: forall h fs a j. ((:-<:) JSStatement fs, InjF fs JSStatementL j) => CxtS h fs a JSAnnotL -> CxtS h fs a JSIdentL -> CxtS h fs a JSSemiL -> CxtS h fs a j
- iJSConstant :: forall h fs a j. ((:-<:) JSStatement fs, InjF fs JSStatementL j) => CxtS h fs a JSAnnotL -> CxtS h fs a (JSCommaList JSExpressionL) -> CxtS h fs a JSSemiL -> CxtS h fs a j
- iJSContinue :: forall h fs a j. ((:-<:) JSStatement fs, InjF fs JSStatementL j) => CxtS h fs a JSAnnotL -> CxtS h fs a JSIdentL -> CxtS h fs a JSSemiL -> CxtS h fs a j
- iJSDoWhile :: forall h fs a j. ((:-<:) JSStatement fs, InjF fs JSStatementL j) => CxtS h fs a JSAnnotL -> CxtS h fs a JSStatementL -> CxtS h fs a JSAnnotL -> CxtS h fs a JSAnnotL -> CxtS h fs a JSExpressionL -> CxtS h fs a JSAnnotL -> CxtS h fs a JSSemiL -> CxtS h fs a j
- iJSFunction :: forall h fs a j. ((:-<:) JSStatement fs, InjF fs JSStatementL j) => CxtS h fs a JSAnnotL -> CxtS h fs a JSIdentL -> CxtS h fs a JSAnnotL -> CxtS h fs a (JSCommaList JSIdentL) -> CxtS h fs a JSAnnotL -> CxtS h fs a JSBlockL -> CxtS h fs a JSSemiL -> CxtS h fs a j
- iJSIf :: forall h fs a j. ((:-<:) JSStatement fs, InjF fs JSStatementL j) => CxtS h fs a JSAnnotL -> CxtS h fs a JSAnnotL -> CxtS h fs a JSExpressionL -> CxtS h fs a JSAnnotL -> CxtS h fs a JSStatementL -> CxtS h fs a j
- iJSIfElse :: forall h fs a j. ((:-<:) JSStatement fs, InjF fs JSStatementL j) => CxtS h fs a JSAnnotL -> CxtS h fs a JSAnnotL -> CxtS h fs a JSExpressionL -> CxtS h fs a JSAnnotL -> CxtS h fs a JSStatementL -> CxtS h fs a JSAnnotL -> CxtS h fs a JSStatementL -> CxtS h fs a j
- iJSLabelled :: forall h fs a j. ((:-<:) JSStatement fs, InjF fs JSStatementL j) => CxtS h fs a JSIdentL -> CxtS h fs a JSAnnotL -> CxtS h fs a JSStatementL -> CxtS h fs a j
- iJSEmptyStatement :: forall h fs a j. ((:-<:) JSStatement fs, InjF fs JSStatementL j) => CxtS h fs a JSAnnotL -> CxtS h fs a j
- iJSExpressionStatement :: forall h fs a j. ((:-<:) JSStatement fs, InjF fs JSStatementL j) => CxtS h fs a JSExpressionL -> CxtS h fs a JSSemiL -> CxtS h fs a j
- iJSAssignStatement :: forall h fs a j. ((:-<:) JSStatement fs, InjF fs JSStatementL j) => CxtS h fs a JSExpressionL -> CxtS h fs a JSAssignOpL -> CxtS h fs a JSExpressionL -> CxtS h fs a JSSemiL -> CxtS h fs a j
- iJSMethodCall :: forall h fs a j. ((:-<:) JSStatement fs, InjF fs JSStatementL j) => CxtS h fs a JSExpressionL -> CxtS h fs a JSAnnotL -> CxtS h fs a (JSCommaList JSExpressionL) -> CxtS h fs a JSAnnotL -> CxtS h fs a JSSemiL -> CxtS h fs a j
- iJSReturn :: forall h fs a j. ((:-<:) JSStatement fs, InjF fs JSStatementL j) => CxtS h fs a JSAnnotL -> CxtS h fs a (Maybe JSExpressionL) -> CxtS h fs a JSSemiL -> CxtS h fs a j
- iJSSwitch :: forall h fs a j. ((:-<:) JSStatement fs, InjF fs JSStatementL j) => CxtS h fs a JSAnnotL -> CxtS h fs a JSAnnotL -> CxtS h fs a JSExpressionL -> CxtS h fs a JSAnnotL -> CxtS h fs a JSAnnotL -> CxtS h fs a [JSSwitchPartsL] -> CxtS h fs a JSAnnotL -> CxtS h fs a JSSemiL -> CxtS h fs a j
- iJSThrow :: forall h fs a j. ((:-<:) JSStatement fs, InjF fs JSStatementL j) => CxtS h fs a JSAnnotL -> CxtS h fs a JSExpressionL -> CxtS h fs a JSSemiL -> CxtS h fs a j
- iJSTry :: forall h fs a j. ((:-<:) JSStatement fs, InjF fs JSStatementL j) => CxtS h fs a JSAnnotL -> CxtS h fs a JSBlockL -> CxtS h fs a [JSTryCatchL] -> CxtS h fs a JSTryFinallyL -> CxtS h fs a j
- iJSVariable :: forall h fs a j. ((:-<:) JSStatement fs, InjF fs JSStatementL j) => CxtS h fs a JSAnnotL -> CxtS h fs a (JSCommaList JSExpressionL) -> CxtS h fs a JSSemiL -> CxtS h fs a j
- iJSWhile :: forall h fs a j. ((:-<:) JSStatement fs, InjF fs JSStatementL j) => CxtS h fs a JSAnnotL -> CxtS h fs a JSAnnotL -> CxtS h fs a JSExpressionL -> CxtS h fs a JSAnnotL -> CxtS h fs a JSStatementL -> CxtS h fs a j
- iJSWith :: forall h fs a j. ((:-<:) JSStatement fs, InjF fs JSStatementL j) => CxtS h fs a JSAnnotL -> CxtS h fs a JSAnnotL -> CxtS h fs a JSExpressionL -> CxtS h fs a JSAnnotL -> CxtS h fs a JSStatementL -> CxtS h fs a JSSemiL -> CxtS h fs a j
- iJSCase :: forall h fs a j. ((:-<:) JSSwitchParts fs, InjF fs JSSwitchPartsL j) => CxtS h fs a JSAnnotL -> CxtS h fs a JSExpressionL -> CxtS h fs a JSAnnotL -> CxtS h fs a [JSStatementL] -> CxtS h fs a j
- iJSDefault :: forall h fs a j. ((:-<:) JSSwitchParts fs, InjF fs JSSwitchPartsL j) => CxtS h fs a JSAnnotL -> CxtS h fs a JSAnnotL -> CxtS h fs a [JSStatementL] -> CxtS h fs a j
- iJSCatch :: forall h fs a j. ((:-<:) JSTryCatch fs, InjF fs JSTryCatchL j) => CxtS h fs a JSAnnotL -> CxtS h fs a JSAnnotL -> CxtS h fs a JSExpressionL -> CxtS h fs a JSAnnotL -> CxtS h fs a JSBlockL -> CxtS h fs a j
- iJSCatchIf :: forall h fs a j. ((:-<:) JSTryCatch fs, InjF fs JSTryCatchL j) => CxtS h fs a JSAnnotL -> CxtS h fs a JSAnnotL -> CxtS h fs a JSExpressionL -> CxtS h fs a JSAnnotL -> CxtS h fs a JSExpressionL -> CxtS h fs a JSAnnotL -> CxtS h fs a JSBlockL -> CxtS h fs a j
- iJSFinally :: forall h fs a j. ((:-<:) JSTryFinally fs, InjF fs JSTryFinallyL j) => CxtS h fs a JSAnnotL -> CxtS h fs a JSBlockL -> CxtS h fs a j
- iJSNoFinally :: forall h fs a j. ((:-<:) JSTryFinally fs, InjF fs JSTryFinallyL j) => CxtS h fs a j
- iJSUnaryOpDecr :: forall h fs a j. ((:-<:) JSUnaryOp fs, InjF fs JSUnaryOpL j) => CxtS h fs a JSAnnotL -> CxtS h fs a j
- iJSUnaryOpDelete :: forall h fs a j. ((:-<:) JSUnaryOp fs, InjF fs JSUnaryOpL j) => CxtS h fs a JSAnnotL -> CxtS h fs a j
- iJSUnaryOpIncr :: forall h fs a j. ((:-<:) JSUnaryOp fs, InjF fs JSUnaryOpL j) => CxtS h fs a JSAnnotL -> CxtS h fs a j
- iJSUnaryOpMinus :: forall h fs a j. ((:-<:) JSUnaryOp fs, InjF fs JSUnaryOpL j) => CxtS h fs a JSAnnotL -> CxtS h fs a j
- iJSUnaryOpNot :: forall h fs a j. ((:-<:) JSUnaryOp fs, InjF fs JSUnaryOpL j) => CxtS h fs a JSAnnotL -> CxtS h fs a j
- iJSUnaryOpPlus :: forall h fs a j. ((:-<:) JSUnaryOp fs, InjF fs JSUnaryOpL j) => CxtS h fs a JSAnnotL -> CxtS h fs a j
- iJSUnaryOpTilde :: forall h fs a j. ((:-<:) JSUnaryOp fs, InjF fs JSUnaryOpL j) => CxtS h fs a JSAnnotL -> CxtS h fs a j
- iJSUnaryOpTypeof :: forall h fs a j. ((:-<:) JSUnaryOp fs, InjF fs JSUnaryOpL j) => CxtS h fs a JSAnnotL -> CxtS h fs a j
- iJSUnaryOpVoid :: forall h fs a j. ((:-<:) JSUnaryOp fs, InjF fs JSUnaryOpL j) => CxtS h fs a JSAnnotL -> CxtS h fs a j
- iTokenPn :: forall h fs a j. ((:-<:) TokenPosn fs, InjF fs TokenPosnL j) => Int -> Int -> Int -> CxtS h fs a j
- iCommentA :: forall h fs a j. ((:-<:) CommentAnnotation fs, InjF fs CommentAnnotationL j) => CxtS h fs a TokenPosnL -> String -> CxtS h fs a j
- iWhiteSpace :: forall h fs a j. ((:-<:) CommentAnnotation fs, InjF fs CommentAnnotationL j) => CxtS h fs a TokenPosnL -> String -> CxtS h fs a j
- iNoComment :: forall h fs a j. ((:-<:) CommentAnnotation fs, InjF fs CommentAnnotationL j) => CxtS h fs a j
- jsSigNames :: [Name]
- data IdentL
- data Ident (e :: * -> *) l where
- data MultiLocalVarDeclCommonAttrsL
- data LocalVarInitL
- data IsOptional
- data OptLocalVarInitL
- data OptLocalVarInit e l where
- data LocalVarDeclAttrsL
- data TupleBinder e l where
- TupleBinder :: e [IdentL] -> TupleBinder e VarDeclBinderL
- data IdentIsVarDeclBinder (e :: Type -> Type) i = i ~ VarDeclBinderL => IdentIsVarDeclBinder (e IdentL)
- data EmptyLocalVarDeclAttrs (e :: * -> *) l where
- data VarDeclBinderL
- data SingleLocalVarDeclL
- data SingleLocalVarDecl e l where
- data EmptyMultiLocalVarDeclCommonAttrs (e :: * -> *) l
- data MultiLocalVarDeclL
- data MultiLocalVarDecl e l where
- data AssignOpL
- data AssignOpEquals (e :: * -> *) l where
- data LhsL
- data RhsL
- data AssignL
- data Assign e l where
- data BlockItemL
- data BlockEndL
- data EmptyBlockEnd (e :: * -> *) l where
- data BlockL
- data Block e l where
- Block :: e [BlockItemL] -> e BlockEndL -> Block e BlockL
- data EmptyBlockItem (e :: * -> *) l where
- pattern Ident' :: (Ident :-<: fs, All HFunctor fs) => String -> CxtS h fs a IdentL
- iIdent :: forall h fs a j. ((:-<:) Ident fs, InjF fs IdentL j) => String -> CxtS h fs a j
- pattern JustLocalVarInit' :: (OptLocalVarInit :-<: fs, All HFunctor fs) => CxtS h fs a LocalVarInitL -> CxtS h fs a OptLocalVarInitL
- iJustLocalVarInit :: forall h fs a j. ((:-<:) OptLocalVarInit fs, InjF fs OptLocalVarInitL j) => CxtS h fs a LocalVarInitL -> CxtS h fs a j
- pattern NoLocalVarInit' :: (OptLocalVarInit :-<: fs, All HFunctor fs) => CxtS h fs a OptLocalVarInitL
- iNoLocalVarInit :: forall h fs a j. ((:-<:) OptLocalVarInit fs, InjF fs OptLocalVarInitL j) => CxtS h fs a j
- pattern EmptyLocalVarDeclAttrs' :: (EmptyLocalVarDeclAttrs :-<: fs, All HFunctor fs) => CxtS h fs a LocalVarDeclAttrsL
- iEmptyLocalVarDeclAttrs :: forall h fs a j. ((:-<:) EmptyLocalVarDeclAttrs fs, InjF fs LocalVarDeclAttrsL j) => CxtS h fs a j
- pattern TupleBinder' :: (TupleBinder :-<: fs, All HFunctor fs) => CxtS h fs a [IdentL] -> CxtS h fs a VarDeclBinderL
- iTupleBinder :: forall h fs a j. ((:-<:) TupleBinder fs, InjF fs VarDeclBinderL j) => CxtS h fs a [IdentL] -> CxtS h fs a j
- pattern IdentIsVarDeclBinder' :: (IdentIsVarDeclBinder :-<: fs, All HFunctor fs) => CxtS h fs a IdentL -> CxtS h fs a VarDeclBinderL
- iIdentIsVarDeclBinder :: forall h fs a j. ((:-<:) IdentIsVarDeclBinder fs, InjF fs VarDeclBinderL j) => CxtS h fs a IdentL -> CxtS h fs a j
- pattern SingleLocalVarDecl' :: (SingleLocalVarDecl :-<: fs, All HFunctor fs) => CxtS h fs a LocalVarDeclAttrsL -> CxtS h fs a VarDeclBinderL -> CxtS h fs a OptLocalVarInitL -> CxtS h fs a SingleLocalVarDeclL
- iSingleLocalVarDecl :: forall h fs a j. ((:-<:) SingleLocalVarDecl fs, InjF fs SingleLocalVarDeclL j) => CxtS h fs a LocalVarDeclAttrsL -> CxtS h fs a VarDeclBinderL -> CxtS h fs a OptLocalVarInitL -> CxtS h fs a j
- pattern EmptyMultiLocalVarDeclCommonAttrs' :: (EmptyMultiLocalVarDeclCommonAttrs :-<: fs, All HFunctor fs) => CxtS h fs a MultiLocalVarDeclCommonAttrsL
- iEmptyMultiLocalVarDeclCommonAttrs :: forall h fs a j. ((:-<:) EmptyMultiLocalVarDeclCommonAttrs fs, InjF fs MultiLocalVarDeclCommonAttrsL j) => CxtS h fs a j
- pattern MultiLocalVarDecl' :: (MultiLocalVarDecl :-<: fs, All HFunctor fs) => CxtS h fs a MultiLocalVarDeclCommonAttrsL -> CxtS h fs a [SingleLocalVarDeclL] -> CxtS h fs a MultiLocalVarDeclL
- iMultiLocalVarDecl :: forall h fs a j. ((:-<:) MultiLocalVarDecl fs, InjF fs MultiLocalVarDeclL j) => CxtS h fs a MultiLocalVarDeclCommonAttrsL -> CxtS h fs a [SingleLocalVarDeclL] -> CxtS h fs a j
- pattern AssignOpEquals' :: (AssignOpEquals :-<: fs, All HFunctor fs) => CxtS h fs a AssignOpL
- iAssignOpEquals :: forall h fs a j. ((:-<:) AssignOpEquals fs, InjF fs AssignOpL j) => CxtS h fs a j
- pattern Assign' :: (Assign :-<: fs, All HFunctor fs) => CxtS h fs a LhsL -> CxtS h fs a AssignOpL -> CxtS h fs a RhsL -> CxtS h fs a AssignL
- iAssign :: forall h fs a j. ((:-<:) Assign fs, InjF fs AssignL j) => CxtS h fs a LhsL -> CxtS h fs a AssignOpL -> CxtS h fs a RhsL -> CxtS h fs a j
- pattern EmptyBlockEnd' :: (EmptyBlockEnd :-<: fs, All HFunctor fs) => CxtS h fs a BlockEndL
- iEmptyBlockEnd :: forall h fs a j. ((:-<:) EmptyBlockEnd fs, InjF fs BlockEndL j) => CxtS h fs a j
- pattern Block' :: (Block :-<: fs, All HFunctor fs) => CxtS h fs a [BlockItemL] -> CxtS h fs a BlockEndL -> CxtS h fs a BlockL
- iBlock :: forall h fs a j. ((:-<:) Block fs, InjF fs BlockL j) => CxtS h fs a [BlockItemL] -> CxtS h fs a BlockEndL -> CxtS h fs a j
- pattern EmptyBlockItem' :: (EmptyBlockItem :-<: fs, All HFunctor fs) => CxtS h fs a BlockItemL
- iEmptyBlockItem :: forall h fs a j. ((:-<:) EmptyBlockItem fs, InjF fs BlockItemL j) => CxtS h fs a j
Documentation
data IdentIsJSExpression (e :: Type -> Type) i Source #
Constructors
i ~ JSExpressionL => IdentIsJSExpression (e IdentL) |
Instances
data JSExpressionIsLocalVarInit (e :: Type -> Type) i Source #
Constructors
i ~ LocalVarInitL => JSExpressionIsLocalVarInit (e JSExpressionL) |
Instances
data JSExpressionIsVarDeclBinder (e :: Type -> Type) i Source #
Constructors
i ~ VarDeclBinderL => JSExpressionIsVarDeclBinder (e JSExpressionL) |
Instances
data MultiLocalVarDeclIsJSStatement (e :: Type -> Type) i Source #
Constructors
i ~ JSStatementL => MultiLocalVarDeclIsJSStatement (e MultiLocalVarDeclL) |
Instances
data JSExpressionIsRhs (e :: Type -> Type) i Source #
Constructors
i ~ RhsL => JSExpressionIsRhs (e JSExpressionL) |
Instances
data JSExpressionIsLhs (e :: Type -> Type) i Source #
Constructors
i ~ LhsL => JSExpressionIsLhs (e JSExpressionL) |
Instances
data JSAssignOpIsAssignOp (e :: Type -> Type) i Source #
Constructors
i ~ AssignOpL => JSAssignOpIsAssignOp (e JSAssignOpL) |
Instances
data AssignIsJSExpression (e :: Type -> Type) i Source #
Constructors
i ~ JSExpressionL => AssignIsJSExpression (e AssignL) |
Instances
data BlockIsJSStatement (e :: Type -> Type) i Source #
Constructors
i ~ JSStatementL => BlockIsJSStatement (e BlockL) |
Instances
data JSStatementIsBlockItem (e :: Type -> Type) i Source #
Constructors
i ~ BlockItemL => JSStatementIsBlockItem (e JSStatementL) |
Instances
data JSBlockIsJSAST (e :: Type -> Type) i Source #
Constructors
i ~ JSASTL => JSBlockIsJSAST (e JSBlockL) |
Instances
iJSBlockIsJSAST :: forall h fs a j. ((:-<:) JSBlockIsJSAST fs, InjF fs JSASTL j) => CxtS h fs a JSBlockL -> CxtS h fs a j Source #
iJSStatementIsBlockItem :: forall h fs a j. ((:-<:) JSStatementIsBlockItem fs, InjF fs BlockItemL j) => CxtS h fs a JSStatementL -> CxtS h fs a j Source #
iBlockIsJSStatement :: forall h fs a j. ((:-<:) BlockIsJSStatement fs, InjF fs JSStatementL j) => CxtS h fs a BlockL -> CxtS h fs a j Source #
iAssignIsJSExpression :: forall h fs a j. ((:-<:) AssignIsJSExpression fs, InjF fs JSExpressionL j) => CxtS h fs a AssignL -> CxtS h fs a j Source #
iJSAssignOpIsAssignOp :: forall h fs a j. ((:-<:) JSAssignOpIsAssignOp fs, InjF fs AssignOpL j) => CxtS h fs a JSAssignOpL -> CxtS h fs a j Source #
iJSExpressionIsLhs :: forall h fs a j. ((:-<:) JSExpressionIsLhs fs, InjF fs LhsL j) => CxtS h fs a JSExpressionL -> CxtS h fs a j Source #
iJSExpressionIsRhs :: forall h fs a j. ((:-<:) JSExpressionIsRhs fs, InjF fs RhsL j) => CxtS h fs a JSExpressionL -> CxtS h fs a j Source #
iMultiLocalVarDeclIsJSStatement :: forall h fs a j. ((:-<:) MultiLocalVarDeclIsJSStatement fs, InjF fs JSStatementL j) => CxtS h fs a MultiLocalVarDeclL -> CxtS h fs a j Source #
iJSExpressionIsVarDeclBinder :: forall h fs a j. ((:-<:) JSExpressionIsVarDeclBinder fs, InjF fs VarDeclBinderL j) => CxtS h fs a JSExpressionL -> CxtS h fs a j Source #
iJSExpressionIsLocalVarInit :: forall h fs a j. ((:-<:) JSExpressionIsLocalVarInit fs, InjF fs LocalVarInitL j) => CxtS h fs a JSExpressionL -> CxtS h fs a j Source #
iIdentIsJSExpression :: forall h fs a j. ((:-<:) IdentIsJSExpression fs, InjF fs JSExpressionL j) => CxtS h fs a IdentL -> CxtS h fs a j Source #
data MaybeIdentIsJSIdent e l where Source #
Constructors
MaybeIdentIsJSIdent :: e (Maybe IdentL) -> MaybeIdentIsJSIdent e JSIdentL |
Instances
iMaybeIdentIsJSIdent :: forall h fs a j. ((:-<:) MaybeIdentIsJSIdent fs, InjF fs JSIdentL j) => CxtS h fs a (Maybe IdentL) -> CxtS h fs a j Source #
pattern JSIdent' :: (MaybeIdentIsJSIdent :-<: fs, Ident :-<: fs, MaybeF :-<: fs, All HFunctor fs) => String -> CxtS h fs a JSIdentL Source #
Constructors
JSFor :: e [JSExpressionL] -> e [JSExpressionL] -> e [JSExpressionL] -> e JSStatementL -> JSFor e JSStatementL | |
JSForIn :: e JSExpressionL -> e JSBinOpL -> e JSExpressionL -> e JSStatementL -> JSFor e JSStatementL | |
JSForVar :: e [SingleLocalVarDeclL] -> e [JSExpressionL] -> e [JSExpressionL] -> e JSStatementL -> JSFor e JSStatementL | |
JSForVarIn :: e SingleLocalVarDeclL -> e JSBinOpL -> e JSExpressionL -> e JSStatementL -> JSFor e JSStatementL |
Instances
iJSForVarIn :: forall h fs a j. ((:-<:) JSFor fs, InjF fs JSStatementL j) => CxtS h fs a SingleLocalVarDeclL -> CxtS h fs a JSBinOpL -> CxtS h fs a JSExpressionL -> CxtS h fs a JSStatementL -> CxtS h fs a j Source #
iJSForVar :: forall h fs a j. ((:-<:) JSFor fs, InjF fs JSStatementL j) => CxtS h fs a [SingleLocalVarDeclL] -> CxtS h fs a [JSExpressionL] -> CxtS h fs a [JSExpressionL] -> CxtS h fs a JSStatementL -> CxtS h fs a j Source #
iJSForIn :: forall h fs a j. ((:-<:) JSFor fs, InjF fs JSStatementL j) => CxtS h fs a JSExpressionL -> CxtS h fs a JSBinOpL -> CxtS h fs a JSExpressionL -> CxtS h fs a JSStatementL -> CxtS h fs a j Source #
iJSFor :: forall h fs a j. ((:-<:) JSFor fs, InjF fs JSStatementL j) => CxtS h fs a [JSExpressionL] -> CxtS h fs a [JSExpressionL] -> CxtS h fs a [JSExpressionL] -> CxtS h fs a JSStatementL -> CxtS h fs a j Source #
data BlockWithPrelude e l where Source #
Constructors
BlockWithPrelude :: [String] -> e BlockL -> BlockWithPrelude e JSBlockL |
Instances
iBlockWithPrelude :: forall h fs a j. ((:-<:) BlockWithPrelude fs, InjF fs JSBlockL j) => [String] -> CxtS h fs a BlockL -> CxtS h fs a j Source #
data FunctionCallIsJSExpression (e :: Type -> Type) i Source #
Constructors
i ~ JSExpressionL => FunctionCallIsJSExpression (e FunctionCallL) |
Instances
data JSExpressionIsPositionalArgExp (e :: Type -> Type) i Source #
Constructors
i ~ PositionalArgExpL => JSExpressionIsPositionalArgExp (e JSExpressionL) |
Instances
data JSExpressionIsFunctionExp (e :: Type -> Type) i Source #
Constructors
i ~ FunctionExpL => JSExpressionIsFunctionExp (e JSExpressionL) |
Instances
data FunctionDefIsJSStatement (e :: Type -> Type) i Source #
Constructors
i ~ JSStatementL => FunctionDefIsJSStatement (e FunctionDefL) |
Instances
data JSBlockIsFunctionBody (e :: Type -> Type) i Source #
Constructors
i ~ FunctionBodyL => JSBlockIsFunctionBody (e JSBlockL) |
Instances
iJSBlockIsFunctionBody :: forall h fs a j. ((:-<:) JSBlockIsFunctionBody fs, InjF fs FunctionBodyL j) => CxtS h fs a JSBlockL -> CxtS h fs a j Source #
iFunctionDefIsJSStatement :: forall h fs a j. ((:-<:) FunctionDefIsJSStatement fs, InjF fs JSStatementL j) => CxtS h fs a FunctionDefL -> CxtS h fs a j Source #
iJSExpressionIsFunctionExp :: forall h fs a j. ((:-<:) JSExpressionIsFunctionExp fs, InjF fs FunctionExpL j) => CxtS h fs a JSExpressionL -> CxtS h fs a j Source #
iJSExpressionIsPositionalArgExp :: forall h fs a j. ((:-<:) JSExpressionIsPositionalArgExp fs, InjF fs PositionalArgExpL j) => CxtS h fs a JSExpressionL -> CxtS h fs a j Source #
iFunctionCallIsJSExpression :: forall h fs a j. ((:-<:) FunctionCallIsJSExpression fs, InjF fs JSExpressionL j) => CxtS h fs a FunctionCallL -> CxtS h fs a j Source #
type MJSSig = '[JSAST, JSAccessor, JSAnnot, JSArrayElement, JSAssignOp, JSBinOp, JSBlock, JSExpression, JSObjectProperty, JSPropertyName, JSSemi, JSStatement, JSSwitchParts, JSTryCatch, JSTryFinally, JSUnaryOp, TokenPosn, CommentAnnotation, ListF, MaybeF, JSCommaListF, JSCommaTrailingListF, IdentIsJSExpression, JSExpressionIsLocalVarInit, JSExpressionIsVarDeclBinder, MultiLocalVarDeclIsJSStatement, JSExpressionIsRhs, JSExpressionIsLhs, JSAssignOpIsAssignOp, AssignIsJSExpression, BlockIsJSStatement, JSStatementIsBlockItem, BlockWithPrelude, JSBlockIsJSAST, FunctionCallIsJSExpression, JSExpressionIsPositionalArgExp, JSExpressionIsFunctionExp, FunctionDefIsJSStatement, JSBlockIsFunctionBody, MaybeIdentIsJSIdent, JSFor, OptLocalVarInit, SingleLocalVarDecl, Ident, AssignOpEquals, Assign, Block, TupleBinder, EmptyLocalVarDeclAttrs, MultiLocalVarDecl, EmptyBlockEnd, EmptyMultiLocalVarDeclCommonAttrs, FunctionCall, EmptyFunctionCallAttrs, FunctionArgumentList, PositionalArgument, FunctionDef, EmptyFunctionDefAttrs, PositionalParameter, EmptyParameterAttrs] Source #
type MJSTermLab = TermLab MJSSig Source #
untranslate :: MJSTerm l -> JSTerm l Source #
data JSCommaTrailingListF e l where Source #
Constructors
JSCTLComma :: e (JSCommaList l) -> e JSAnnotL -> JSCommaTrailingListF e (JSCommaTrailingList l) | |
JSCTLNone :: e (JSCommaList l) -> JSCommaTrailingListF e (JSCommaTrailingList l) |
Instances
type JSCommaTrailingList l = JSCommaTrailingList l Source #
data JSCommaListF e l where Source #
Constructors
JSLCons :: e (JSCommaList l) -> e JSAnnotL -> e l -> JSCommaListF e (JSCommaList l) | |
JSLOne :: e l -> JSCommaListF e (JSCommaList l) | |
JSLNil :: JSCommaListF e (JSCommaList t) |
Instances
type JSCommaList l = JSCommaList l Source #
data CommentAnnotationL Source #
Instances
KDynCase CommentAnnotation CommentAnnotationL Source # | |
Defined in Cubix.Language.JavaScript.Parametric.Full.Types Methods kdyncase :: forall (e :: Type -> Type) b. CommentAnnotation e b -> Maybe (b :~: CommentAnnotationL) # |
data CommentAnnotation (e :: Type -> Type) i Source #
Constructors
i ~ CommentAnnotationL => CommentA (e TokenPosnL) String | |
i ~ CommentAnnotationL => WhiteSpace (e TokenPosnL) String | |
i ~ CommentAnnotationL => NoComment |
Instances
data TokenPosnL Source #
Instances
data TokenPosn (e :: Type -> Type) i Source #
Constructors
i ~ TokenPosnL => TokenPn !Int !Int !Int |
Instances
data JSVarInitializerL Source #
pattern JSVarInit :: () => i ~ JSVarInitializerL => !(e JSAnnotL) -> !(e JSExpressionL) -> JSVarInitializer e i Source #
pattern JSVarInitNone :: () => i ~ JSVarInitializerL => JSVarInitializer e i Source #
data JSUnaryOpL Source #
Instances
data JSUnaryOp (e :: Type -> Type) i Source #
Constructors
i ~ JSUnaryOpL => JSUnaryOpDecr !(e JSAnnotL) | |
i ~ JSUnaryOpL => JSUnaryOpDelete !(e JSAnnotL) | |
i ~ JSUnaryOpL => JSUnaryOpIncr !(e JSAnnotL) | |
i ~ JSUnaryOpL => JSUnaryOpMinus !(e JSAnnotL) | |
i ~ JSUnaryOpL => JSUnaryOpNot !(e JSAnnotL) | |
i ~ JSUnaryOpL => JSUnaryOpPlus !(e JSAnnotL) | |
i ~ JSUnaryOpL => JSUnaryOpTilde !(e JSAnnotL) | |
i ~ JSUnaryOpL => JSUnaryOpTypeof !(e JSAnnotL) | |
i ~ JSUnaryOpL => JSUnaryOpVoid !(e JSAnnotL) |
Instances
data JSTryFinallyL Source #
Instances
KDynCase JSTryFinally JSTryFinallyL Source # | |
Defined in Cubix.Language.JavaScript.Parametric.Full.Types Methods kdyncase :: forall (e :: Type -> Type) b. JSTryFinally e b -> Maybe (b :~: JSTryFinallyL) # |
data JSTryFinally (e :: Type -> Type) i Source #
Constructors
i ~ JSTryFinallyL => JSFinally !(e JSAnnotL) !(e JSBlockL) | |
i ~ JSTryFinallyL => JSNoFinally |
Instances
data JSTryCatchL Source #
Instances
KDynCase JSTryCatch JSTryCatchL Source # | |
Defined in Cubix.Language.JavaScript.Parametric.Full.Types Methods kdyncase :: forall (e :: Type -> Type) b. JSTryCatch e b -> Maybe (b :~: JSTryCatchL) # |
data JSTryCatch (e :: Type -> Type) i Source #
Constructors
i ~ JSTryCatchL => JSCatch !(e JSAnnotL) !(e JSAnnotL) !(e JSExpressionL) !(e JSAnnotL) !(e JSBlockL) | |
i ~ JSTryCatchL => JSCatchIf !(e JSAnnotL) !(e JSAnnotL) !(e JSExpressionL) !(e JSAnnotL) !(e JSExpressionL) !(e JSAnnotL) !(e JSBlockL) |
Instances
data JSSwitchPartsL Source #
Instances
KDynCase JSSwitchParts JSSwitchPartsL Source # | |
Defined in Cubix.Language.JavaScript.Parametric.Full.Types Methods kdyncase :: forall (e :: Type -> Type) b. JSSwitchParts e b -> Maybe (b :~: JSSwitchPartsL) # |
data JSSwitchParts (e :: Type -> Type) i Source #
Constructors
i ~ JSSwitchPartsL => JSCase !(e JSAnnotL) !(e JSExpressionL) !(e JSAnnotL) !(e [JSStatementL]) | |
i ~ JSSwitchPartsL => JSDefault !(e JSAnnotL) !(e JSAnnotL) !(e [JSStatementL]) |
Instances
data JSStatementL Source #
Instances
data JSStatement (e :: Type -> Type) i Source #
Constructors
Instances
data JSSemi (e :: Type -> Type) i Source #
Constructors
i ~ JSSemiL => JSSemi !(e JSAnnotL) | |
i ~ JSSemiL => JSSemiAuto |
Instances
data JSPropertyNameL Source #
Instances
KDynCase JSPropertyName JSPropertyNameL Source # | |
Defined in Cubix.Language.JavaScript.Parametric.Full.Types Methods kdyncase :: forall (e :: Type -> Type) b. JSPropertyName e b -> Maybe (b :~: JSPropertyNameL) # |
data JSPropertyName (e :: Type -> Type) i Source #
Constructors
i ~ JSPropertyNameL => JSPropertyIdent !(e JSAnnotL) !String | |
i ~ JSPropertyNameL => JSPropertyString !(e JSAnnotL) !String | |
i ~ JSPropertyNameL => JSPropertyNumber !(e JSAnnotL) !String |
Instances
data JSObjectPropertyL Source #
Instances
KDynCase JSObjectProperty JSObjectPropertyL Source # | |
Defined in Cubix.Language.JavaScript.Parametric.Full.Types Methods kdyncase :: forall (e :: Type -> Type) b. JSObjectProperty e b -> Maybe (b :~: JSObjectPropertyL) # |
data JSObjectProperty (e :: Type -> Type) i Source #
Constructors
i ~ JSObjectPropertyL => JSPropertyAccessor !(e JSAccessorL) !(e JSPropertyNameL) !(e JSAnnotL) !(e [JSExpressionL]) !(e JSAnnotL) !(e JSBlockL) | |
i ~ JSObjectPropertyL => JSPropertyNameandValue !(e JSPropertyNameL) !(e JSAnnotL) !(e [JSExpressionL]) |
Instances
Instances
KDynCase MaybeIdentIsJSIdent JSIdentL Source # | |
InjF MJSSig (Maybe IdentL) JSIdentL Source # | |
Defined in Cubix.Language.JavaScript.Parametric.Common.Types Methods injF :: forall h (a :: Type -> Type). CxtS h MJSSig a (Maybe IdentL) -> CxtS h MJSSig a JSIdentL Source # projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MJSSig :&: p) a JSIdentL -> Maybe (Cxt h (Sum MJSSig :&: p) a (Maybe IdentL)) Source # projF :: forall h (a :: Type -> Type). CxtS h MJSSig a JSIdentL -> Maybe (CxtS h MJSSig a (Maybe IdentL)) Source # |
pattern JSIdentNone :: () => i ~ JSIdentL => JSIdent e i Source #
data JSExpressionL Source #
Instances
data JSExpression (e :: Type -> Type) i Source #
Constructors
Instances
Instances
data JSBlock (e :: Type -> Type) i Source #
Constructors
i ~ JSBlockL => JSBlock !(e JSAnnotL) !(e [JSStatementL]) !(e JSAnnotL) |
Instances
data JSBinOp (e :: Type -> Type) i Source #
Constructors
i ~ JSBinOpL => JSBinOpAnd !(e JSAnnotL) | |
i ~ JSBinOpL => JSBinOpBitAnd !(e JSAnnotL) | |
i ~ JSBinOpL => JSBinOpBitOr !(e JSAnnotL) | |
i ~ JSBinOpL => JSBinOpBitXor !(e JSAnnotL) | |
i ~ JSBinOpL => JSBinOpDivide !(e JSAnnotL) | |
i ~ JSBinOpL => JSBinOpEq !(e JSAnnotL) | |
i ~ JSBinOpL => JSBinOpGe !(e JSAnnotL) | |
i ~ JSBinOpL => JSBinOpGt !(e JSAnnotL) | |
i ~ JSBinOpL => JSBinOpIn !(e JSAnnotL) | |
i ~ JSBinOpL => JSBinOpInstanceOf !(e JSAnnotL) | |
i ~ JSBinOpL => JSBinOpLe !(e JSAnnotL) | |
i ~ JSBinOpL => JSBinOpLsh !(e JSAnnotL) | |
i ~ JSBinOpL => JSBinOpLt !(e JSAnnotL) | |
i ~ JSBinOpL => JSBinOpMinus !(e JSAnnotL) | |
i ~ JSBinOpL => JSBinOpMod !(e JSAnnotL) | |
i ~ JSBinOpL => JSBinOpNeq !(e JSAnnotL) | |
i ~ JSBinOpL => JSBinOpOr !(e JSAnnotL) | |
i ~ JSBinOpL => JSBinOpPlus !(e JSAnnotL) | |
i ~ JSBinOpL => JSBinOpRsh !(e JSAnnotL) | |
i ~ JSBinOpL => JSBinOpStrictEq !(e JSAnnotL) | |
i ~ JSBinOpL => JSBinOpStrictNeq !(e JSAnnotL) | |
i ~ JSBinOpL => JSBinOpTimes !(e JSAnnotL) | |
i ~ JSBinOpL => JSBinOpUrsh !(e JSAnnotL) |
Instances
data JSAssignOpL Source #
Instances
KDynCase JSAssignOp JSAssignOpL Source # | |
Defined in Cubix.Language.JavaScript.Parametric.Full.Types Methods kdyncase :: forall (e :: Type -> Type) b. JSAssignOp e b -> Maybe (b :~: JSAssignOpL) # | |
(JSAssignOpIsAssignOp :-<: fs, All HFunctor fs) => InjF fs JSAssignOpL AssignOpL Source # | |
Defined in Cubix.Language.JavaScript.Parametric.Common.Types Methods injF :: forall h (a :: Type -> Type). CxtS h fs a JSAssignOpL -> CxtS h fs a AssignOpL Source # projF' :: forall h p (a :: Type -> Type). Cxt h (Sum fs :&: p) a AssignOpL -> Maybe (Cxt h (Sum fs :&: p) a JSAssignOpL) Source # projF :: forall h (a :: Type -> Type). CxtS h fs a AssignOpL -> Maybe (CxtS h fs a JSAssignOpL) Source # |
data JSAssignOp (e :: Type -> Type) i Source #
Constructors
i ~ JSAssignOpL => JSAssign !(e JSAnnotL) | |
i ~ JSAssignOpL => JSTimesAssign !(e JSAnnotL) | |
i ~ JSAssignOpL => JSDivideAssign !(e JSAnnotL) | |
i ~ JSAssignOpL => JSModAssign !(e JSAnnotL) | |
i ~ JSAssignOpL => JSPlusAssign !(e JSAnnotL) | |
i ~ JSAssignOpL => JSMinusAssign !(e JSAnnotL) | |
i ~ JSAssignOpL => JSLshAssign !(e JSAnnotL) | |
i ~ JSAssignOpL => JSRshAssign !(e JSAnnotL) | |
i ~ JSAssignOpL => JSUrshAssign !(e JSAnnotL) | |
i ~ JSAssignOpL => JSBwAndAssign !(e JSAnnotL) | |
i ~ JSAssignOpL => JSBwXorAssign !(e JSAnnotL) | |
i ~ JSAssignOpL => JSBwOrAssign !(e JSAnnotL) |
Instances
data JSArrayElementL Source #
Instances
KDynCase JSArrayElement JSArrayElementL Source # | |
Defined in Cubix.Language.JavaScript.Parametric.Full.Types Methods kdyncase :: forall (e :: Type -> Type) b. JSArrayElement e b -> Maybe (b :~: JSArrayElementL) # |
data JSArrayElement (e :: Type -> Type) i Source #
Constructors
i ~ JSArrayElementL => JSArrayElement !(e JSExpressionL) | |
i ~ JSArrayElementL => JSArrayComma !(e JSAnnotL) |
Instances
data JSAnnot (e :: Type -> Type) i Source #
Constructors
i ~ JSAnnotL => JSAnnot !(e TokenPosnL) !(e [CommentAnnotationL]) | |
i ~ JSAnnotL => JSAnnotSpace | |
i ~ JSAnnotL => JSNoAnnot |
Instances
data JSAccessorL Source #
Instances
KDynCase JSAccessor JSAccessorL Source # | |
Defined in Cubix.Language.JavaScript.Parametric.Full.Types Methods kdyncase :: forall (e :: Type -> Type) b. JSAccessor e b -> Maybe (b :~: JSAccessorL) # |
data JSAccessor (e :: Type -> Type) i Source #
Constructors
i ~ JSAccessorL => JSAccessorGet !(e JSAnnotL) | |
i ~ JSAccessorL => JSAccessorSet !(e JSAnnotL) |
Instances
Instances
KDynCase JSAST JSASTL Source # | |
KDynCase JSBlockIsJSAST JSASTL Source # | |
(JSBlockIsJSAST :-<: fs, All HFunctor fs) => InjF fs JSBlockL JSASTL Source # | |
Defined in Cubix.Language.JavaScript.Parametric.Common.Types Methods injF :: forall h (a :: Type -> Type). CxtS h fs a JSBlockL -> CxtS h fs a JSASTL Source # projF' :: forall h p (a :: Type -> Type). Cxt h (Sum fs :&: p) a JSASTL -> Maybe (Cxt h (Sum fs :&: p) a JSBlockL) Source # projF :: forall h (a :: Type -> Type). CxtS h fs a JSASTL -> Maybe (CxtS h fs a JSBlockL) Source # |
data JSAST (e :: Type -> Type) i Source #
Constructors
i ~ JSASTL => JSAstProgram !(e [JSStatementL]) !(e JSAnnotL) | |
i ~ JSASTL => JSAstStatement !(e JSStatementL) !(e JSAnnotL) | |
i ~ JSASTL => JSAstExpression !(e JSExpressionL) !(e JSAnnotL) | |
i ~ JSASTL => JSAstLiteral !(e JSExpressionL) !(e JSAnnotL) |
Instances
riJSLCons :: JSCommaListF :<: f => Cxt h f a (JSCommaList l) -> Cxt h f a JSAnnotL -> Cxt h f a l -> Cxt h f a (JSCommaList l) Source #
riJSLOne :: JSCommaListF :<: f => Cxt h f a l -> Cxt h f a (JSCommaList l) Source #
riJSLNil :: JSCommaListF :<: f => Cxt h f a (JSCommaList l) Source #
riJSCTLComma :: JSCommaTrailingListF :<: f => Cxt h f a (JSCommaList l) -> Cxt h f a JSAnnotL -> Cxt h f a (JSCommaTrailingList l) Source #
riJSCTLNone :: JSCommaTrailingListF :<: f => Cxt h f a (JSCommaList l) -> Cxt h f a (JSCommaTrailingList l) Source #
type JSSig = '[JSAST, JSAccessor, JSAnnot, JSArrayElement, JSAssignOp, JSBinOp, JSBlock, JSExpression, JSIdent, JSObjectProperty, JSPropertyName, JSSemi, JSStatement, JSSwitchParts, JSTryCatch, JSTryFinally, JSUnaryOp, JSVarInitializer, TokenPosn, CommentAnnotation, ListF, MaybeF, JSCommaListF, JSCommaTrailingListF] Source #
iJSAstProgram :: forall h fs a j. ((:-<:) JSAST fs, InjF fs JSASTL j) => CxtS h fs a [JSStatementL] -> CxtS h fs a JSAnnotL -> CxtS h fs a j Source #
iJSAstStatement :: forall h fs a j. ((:-<:) JSAST fs, InjF fs JSASTL j) => CxtS h fs a JSStatementL -> CxtS h fs a JSAnnotL -> CxtS h fs a j Source #
iJSAstExpression :: forall h fs a j. ((:-<:) JSAST fs, InjF fs JSASTL j) => CxtS h fs a JSExpressionL -> CxtS h fs a JSAnnotL -> CxtS h fs a j Source #
iJSAstLiteral :: forall h fs a j. ((:-<:) JSAST fs, InjF fs JSASTL j) => CxtS h fs a JSExpressionL -> CxtS h fs a JSAnnotL -> CxtS h fs a j Source #
iJSAccessorGet :: forall h fs a j. ((:-<:) JSAccessor fs, InjF fs JSAccessorL j) => CxtS h fs a JSAnnotL -> CxtS h fs a j Source #
iJSAccessorSet :: forall h fs a j. ((:-<:) JSAccessor fs, InjF fs JSAccessorL j) => CxtS h fs a JSAnnotL -> CxtS h fs a j Source #
iJSAnnot :: forall h fs a j. ((:-<:) JSAnnot fs, InjF fs JSAnnotL j) => CxtS h fs a TokenPosnL -> CxtS h fs a [CommentAnnotationL] -> CxtS h fs a j Source #
iJSArrayElement :: forall h fs a j. ((:-<:) JSArrayElement fs, InjF fs JSArrayElementL j) => CxtS h fs a JSExpressionL -> CxtS h fs a j Source #
iJSArrayComma :: forall h fs a j. ((:-<:) JSArrayElement fs, InjF fs JSArrayElementL j) => CxtS h fs a JSAnnotL -> CxtS h fs a j Source #
iJSAssign :: forall h fs a j. ((:-<:) JSAssignOp fs, InjF fs JSAssignOpL j) => CxtS h fs a JSAnnotL -> CxtS h fs a j Source #
iJSTimesAssign :: forall h fs a j. ((:-<:) JSAssignOp fs, InjF fs JSAssignOpL j) => CxtS h fs a JSAnnotL -> CxtS h fs a j Source #
iJSDivideAssign :: forall h fs a j. ((:-<:) JSAssignOp fs, InjF fs JSAssignOpL j) => CxtS h fs a JSAnnotL -> CxtS h fs a j Source #
iJSModAssign :: forall h fs a j. ((:-<:) JSAssignOp fs, InjF fs JSAssignOpL j) => CxtS h fs a JSAnnotL -> CxtS h fs a j Source #
iJSPlusAssign :: forall h fs a j. ((:-<:) JSAssignOp fs, InjF fs JSAssignOpL j) => CxtS h fs a JSAnnotL -> CxtS h fs a j Source #
iJSMinusAssign :: forall h fs a j. ((:-<:) JSAssignOp fs, InjF fs JSAssignOpL j) => CxtS h fs a JSAnnotL -> CxtS h fs a j Source #
iJSLshAssign :: forall h fs a j. ((:-<:) JSAssignOp fs, InjF fs JSAssignOpL j) => CxtS h fs a JSAnnotL -> CxtS h fs a j Source #
iJSRshAssign :: forall h fs a j. ((:-<:) JSAssignOp fs, InjF fs JSAssignOpL j) => CxtS h fs a JSAnnotL -> CxtS h fs a j Source #
iJSUrshAssign :: forall h fs a j. ((:-<:) JSAssignOp fs, InjF fs JSAssignOpL j) => CxtS h fs a JSAnnotL -> CxtS h fs a j Source #
iJSBwAndAssign :: forall h fs a j. ((:-<:) JSAssignOp fs, InjF fs JSAssignOpL j) => CxtS h fs a JSAnnotL -> CxtS h fs a j Source #
iJSBwXorAssign :: forall h fs a j. ((:-<:) JSAssignOp fs, InjF fs JSAssignOpL j) => CxtS h fs a JSAnnotL -> CxtS h fs a j Source #
iJSBwOrAssign :: forall h fs a j. ((:-<:) JSAssignOp fs, InjF fs JSAssignOpL j) => CxtS h fs a JSAnnotL -> CxtS h fs a j Source #
iJSBinOpAnd :: forall h fs a j. ((:-<:) JSBinOp fs, InjF fs JSBinOpL j) => CxtS h fs a JSAnnotL -> CxtS h fs a j Source #
iJSBinOpBitAnd :: forall h fs a j. ((:-<:) JSBinOp fs, InjF fs JSBinOpL j) => CxtS h fs a JSAnnotL -> CxtS h fs a j Source #
iJSBinOpBitOr :: forall h fs a j. ((:-<:) JSBinOp fs, InjF fs JSBinOpL j) => CxtS h fs a JSAnnotL -> CxtS h fs a j Source #
iJSBinOpBitXor :: forall h fs a j. ((:-<:) JSBinOp fs, InjF fs JSBinOpL j) => CxtS h fs a JSAnnotL -> CxtS h fs a j Source #
iJSBinOpDivide :: forall h fs a j. ((:-<:) JSBinOp fs, InjF fs JSBinOpL j) => CxtS h fs a JSAnnotL -> CxtS h fs a j Source #
iJSBinOpEq :: forall h fs a j. ((:-<:) JSBinOp fs, InjF fs JSBinOpL j) => CxtS h fs a JSAnnotL -> CxtS h fs a j Source #
iJSBinOpGe :: forall h fs a j. ((:-<:) JSBinOp fs, InjF fs JSBinOpL j) => CxtS h fs a JSAnnotL -> CxtS h fs a j Source #
iJSBinOpGt :: forall h fs a j. ((:-<:) JSBinOp fs, InjF fs JSBinOpL j) => CxtS h fs a JSAnnotL -> CxtS h fs a j Source #
iJSBinOpIn :: forall h fs a j. ((:-<:) JSBinOp fs, InjF fs JSBinOpL j) => CxtS h fs a JSAnnotL -> CxtS h fs a j Source #
iJSBinOpInstanceOf :: forall h fs a j. ((:-<:) JSBinOp fs, InjF fs JSBinOpL j) => CxtS h fs a JSAnnotL -> CxtS h fs a j Source #
iJSBinOpLe :: forall h fs a j. ((:-<:) JSBinOp fs, InjF fs JSBinOpL j) => CxtS h fs a JSAnnotL -> CxtS h fs a j Source #
iJSBinOpLsh :: forall h fs a j. ((:-<:) JSBinOp fs, InjF fs JSBinOpL j) => CxtS h fs a JSAnnotL -> CxtS h fs a j Source #
iJSBinOpLt :: forall h fs a j. ((:-<:) JSBinOp fs, InjF fs JSBinOpL j) => CxtS h fs a JSAnnotL -> CxtS h fs a j Source #
iJSBinOpMinus :: forall h fs a j. ((:-<:) JSBinOp fs, InjF fs JSBinOpL j) => CxtS h fs a JSAnnotL -> CxtS h fs a j Source #
iJSBinOpMod :: forall h fs a j. ((:-<:) JSBinOp fs, InjF fs JSBinOpL j) => CxtS h fs a JSAnnotL -> CxtS h fs a j Source #
iJSBinOpNeq :: forall h fs a j. ((:-<:) JSBinOp fs, InjF fs JSBinOpL j) => CxtS h fs a JSAnnotL -> CxtS h fs a j Source #
iJSBinOpOr :: forall h fs a j. ((:-<:) JSBinOp fs, InjF fs JSBinOpL j) => CxtS h fs a JSAnnotL -> CxtS h fs a j Source #
iJSBinOpPlus :: forall h fs a j. ((:-<:) JSBinOp fs, InjF fs JSBinOpL j) => CxtS h fs a JSAnnotL -> CxtS h fs a j Source #
iJSBinOpRsh :: forall h fs a j. ((:-<:) JSBinOp fs, InjF fs JSBinOpL j) => CxtS h fs a JSAnnotL -> CxtS h fs a j Source #
iJSBinOpStrictEq :: forall h fs a j. ((:-<:) JSBinOp fs, InjF fs JSBinOpL j) => CxtS h fs a JSAnnotL -> CxtS h fs a j Source #
iJSBinOpStrictNeq :: forall h fs a j. ((:-<:) JSBinOp fs, InjF fs JSBinOpL j) => CxtS h fs a JSAnnotL -> CxtS h fs a j Source #
iJSBinOpTimes :: forall h fs a j. ((:-<:) JSBinOp fs, InjF fs JSBinOpL j) => CxtS h fs a JSAnnotL -> CxtS h fs a j Source #
iJSBinOpUrsh :: forall h fs a j. ((:-<:) JSBinOp fs, InjF fs JSBinOpL j) => CxtS h fs a JSAnnotL -> CxtS h fs a j Source #
iJSBlock :: forall h fs a j. ((:-<:) JSBlock fs, InjF fs JSBlockL j) => CxtS h fs a JSAnnotL -> CxtS h fs a [JSStatementL] -> CxtS h fs a JSAnnotL -> CxtS h fs a j Source #
iJSIdentifier :: forall h fs a j. ((:-<:) JSExpression fs, InjF fs JSExpressionL j) => CxtS h fs a JSAnnotL -> String -> CxtS h fs a j Source #
iJSDecimal :: forall h fs a j. ((:-<:) JSExpression fs, InjF fs JSExpressionL j) => CxtS h fs a JSAnnotL -> String -> CxtS h fs a j Source #
iJSLiteral :: forall h fs a j. ((:-<:) JSExpression fs, InjF fs JSExpressionL j) => CxtS h fs a JSAnnotL -> String -> CxtS h fs a j Source #
iJSHexInteger :: forall h fs a j. ((:-<:) JSExpression fs, InjF fs JSExpressionL j) => CxtS h fs a JSAnnotL -> String -> CxtS h fs a j Source #
iJSOctal :: forall h fs a j. ((:-<:) JSExpression fs, InjF fs JSExpressionL j) => CxtS h fs a JSAnnotL -> String -> CxtS h fs a j Source #
iJSStringLiteral :: forall h fs a j. ((:-<:) JSExpression fs, InjF fs JSExpressionL j) => CxtS h fs a JSAnnotL -> String -> CxtS h fs a j Source #
iJSRegEx :: forall h fs a j. ((:-<:) JSExpression fs, InjF fs JSExpressionL j) => CxtS h fs a JSAnnotL -> String -> CxtS h fs a j Source #
iJSArrayLiteral :: forall h fs a j. ((:-<:) JSExpression fs, InjF fs JSExpressionL j) => CxtS h fs a JSAnnotL -> CxtS h fs a [JSArrayElementL] -> CxtS h fs a JSAnnotL -> CxtS h fs a j Source #
iJSAssignExpression :: forall h fs a j. ((:-<:) JSExpression fs, InjF fs JSExpressionL j) => CxtS h fs a JSExpressionL -> CxtS h fs a JSAssignOpL -> CxtS h fs a JSExpressionL -> CxtS h fs a j Source #
iJSCallExpression :: forall h fs a j. ((:-<:) JSExpression fs, InjF fs JSExpressionL j) => CxtS h fs a JSExpressionL -> CxtS h fs a JSAnnotL -> CxtS h fs a (JSCommaList JSExpressionL) -> CxtS h fs a JSAnnotL -> CxtS h fs a j Source #
iJSCallExpressionDot :: forall h fs a j. ((:-<:) JSExpression fs, InjF fs JSExpressionL j) => CxtS h fs a JSExpressionL -> CxtS h fs a JSAnnotL -> CxtS h fs a JSExpressionL -> CxtS h fs a j Source #
iJSCallExpressionSquare :: forall h fs a j. ((:-<:) JSExpression fs, InjF fs JSExpressionL j) => CxtS h fs a JSExpressionL -> CxtS h fs a JSAnnotL -> CxtS h fs a JSExpressionL -> CxtS h fs a JSAnnotL -> CxtS h fs a j Source #
iJSCommaExpression :: forall h fs a j. ((:-<:) JSExpression fs, InjF fs JSExpressionL j) => CxtS h fs a JSExpressionL -> CxtS h fs a JSAnnotL -> CxtS h fs a JSExpressionL -> CxtS h fs a j Source #
iJSExpressionBinary :: forall h fs a j. ((:-<:) JSExpression fs, InjF fs JSExpressionL j) => CxtS h fs a JSExpressionL -> CxtS h fs a JSBinOpL -> CxtS h fs a JSExpressionL -> CxtS h fs a j Source #
iJSExpressionParen :: forall h fs a j. ((:-<:) JSExpression fs, InjF fs JSExpressionL j) => CxtS h fs a JSAnnotL -> CxtS h fs a JSExpressionL -> CxtS h fs a JSAnnotL -> CxtS h fs a j Source #
iJSExpressionPostfix :: forall h fs a j. ((:-<:) JSExpression fs, InjF fs JSExpressionL j) => CxtS h fs a JSExpressionL -> CxtS h fs a JSUnaryOpL -> CxtS h fs a j Source #
iJSExpressionTernary :: forall h fs a j. ((:-<:) JSExpression fs, InjF fs JSExpressionL j) => CxtS h fs a JSExpressionL -> CxtS h fs a JSAnnotL -> CxtS h fs a JSExpressionL -> CxtS h fs a JSAnnotL -> CxtS h fs a JSExpressionL -> CxtS h fs a j Source #
iJSFunctionExpression :: forall h fs a j. ((:-<:) JSExpression fs, InjF fs JSExpressionL j) => CxtS h fs a JSAnnotL -> CxtS h fs a JSIdentL -> CxtS h fs a JSAnnotL -> CxtS h fs a (JSCommaList JSIdentL) -> CxtS h fs a JSAnnotL -> CxtS h fs a JSBlockL -> CxtS h fs a j Source #
iJSMemberDot :: forall h fs a j. ((:-<:) JSExpression fs, InjF fs JSExpressionL j) => CxtS h fs a JSExpressionL -> CxtS h fs a JSAnnotL -> CxtS h fs a JSExpressionL -> CxtS h fs a j Source #
iJSMemberExpression :: forall h fs a j. ((:-<:) JSExpression fs, InjF fs JSExpressionL j) => CxtS h fs a JSExpressionL -> CxtS h fs a JSAnnotL -> CxtS h fs a (JSCommaList JSExpressionL) -> CxtS h fs a JSAnnotL -> CxtS h fs a j Source #
iJSMemberNew :: forall h fs a j. ((:-<:) JSExpression fs, InjF fs JSExpressionL j) => CxtS h fs a JSAnnotL -> CxtS h fs a JSExpressionL -> CxtS h fs a JSAnnotL -> CxtS h fs a (JSCommaList JSExpressionL) -> CxtS h fs a JSAnnotL -> CxtS h fs a j Source #
iJSMemberSquare :: forall h fs a j. ((:-<:) JSExpression fs, InjF fs JSExpressionL j) => CxtS h fs a JSExpressionL -> CxtS h fs a JSAnnotL -> CxtS h fs a JSExpressionL -> CxtS h fs a JSAnnotL -> CxtS h fs a j Source #
iJSNewExpression :: forall h fs a j. ((:-<:) JSExpression fs, InjF fs JSExpressionL j) => CxtS h fs a JSAnnotL -> CxtS h fs a JSExpressionL -> CxtS h fs a j Source #
iJSObjectLiteral :: forall h fs a j. ((:-<:) JSExpression fs, InjF fs JSExpressionL j) => CxtS h fs a JSAnnotL -> CxtS h fs a (JSCommaTrailingList JSObjectPropertyL) -> CxtS h fs a JSAnnotL -> CxtS h fs a j Source #
iJSUnaryExpression :: forall h fs a j. ((:-<:) JSExpression fs, InjF fs JSExpressionL j) => CxtS h fs a JSUnaryOpL -> CxtS h fs a JSExpressionL -> CxtS h fs a j Source #
iJSVarInitExpression :: forall h fs a j. ((:-<:) JSExpression fs, InjF fs JSExpressionL j) => CxtS h fs a JSExpressionL -> CxtS h fs a JSVarInitializerL -> CxtS h fs a j Source #
iJSPropertyAccessor :: forall h fs a j. ((:-<:) JSObjectProperty fs, InjF fs JSObjectPropertyL j) => CxtS h fs a JSAccessorL -> CxtS h fs a JSPropertyNameL -> CxtS h fs a JSAnnotL -> CxtS h fs a [JSExpressionL] -> CxtS h fs a JSAnnotL -> CxtS h fs a JSBlockL -> CxtS h fs a j Source #
iJSPropertyNameandValue :: forall h fs a j. ((:-<:) JSObjectProperty fs, InjF fs JSObjectPropertyL j) => CxtS h fs a JSPropertyNameL -> CxtS h fs a JSAnnotL -> CxtS h fs a [JSExpressionL] -> CxtS h fs a j Source #
iJSPropertyIdent :: forall h fs a j. ((:-<:) JSPropertyName fs, InjF fs JSPropertyNameL j) => CxtS h fs a JSAnnotL -> String -> CxtS h fs a j Source #
iJSPropertyString :: forall h fs a j. ((:-<:) JSPropertyName fs, InjF fs JSPropertyNameL j) => CxtS h fs a JSAnnotL -> String -> CxtS h fs a j Source #
iJSPropertyNumber :: forall h fs a j. ((:-<:) JSPropertyName fs, InjF fs JSPropertyNameL j) => CxtS h fs a JSAnnotL -> String -> CxtS h fs a j Source #
iJSSemi :: forall h fs a j. ((:-<:) JSSemi fs, InjF fs JSSemiL j) => CxtS h fs a JSAnnotL -> CxtS h fs a j Source #
iJSStatementBlock :: forall h fs a j. ((:-<:) JSStatement fs, InjF fs JSStatementL j) => CxtS h fs a JSAnnotL -> CxtS h fs a [JSStatementL] -> CxtS h fs a JSAnnotL -> CxtS h fs a JSSemiL -> CxtS h fs a j Source #
iJSBreak :: forall h fs a j. ((:-<:) JSStatement fs, InjF fs JSStatementL j) => CxtS h fs a JSAnnotL -> CxtS h fs a JSIdentL -> CxtS h fs a JSSemiL -> CxtS h fs a j Source #
iJSConstant :: forall h fs a j. ((:-<:) JSStatement fs, InjF fs JSStatementL j) => CxtS h fs a JSAnnotL -> CxtS h fs a (JSCommaList JSExpressionL) -> CxtS h fs a JSSemiL -> CxtS h fs a j Source #
iJSContinue :: forall h fs a j. ((:-<:) JSStatement fs, InjF fs JSStatementL j) => CxtS h fs a JSAnnotL -> CxtS h fs a JSIdentL -> CxtS h fs a JSSemiL -> CxtS h fs a j Source #
iJSDoWhile :: forall h fs a j. ((:-<:) JSStatement fs, InjF fs JSStatementL j) => CxtS h fs a JSAnnotL -> CxtS h fs a JSStatementL -> CxtS h fs a JSAnnotL -> CxtS h fs a JSAnnotL -> CxtS h fs a JSExpressionL -> CxtS h fs a JSAnnotL -> CxtS h fs a JSSemiL -> CxtS h fs a j Source #
iJSFunction :: forall h fs a j. ((:-<:) JSStatement fs, InjF fs JSStatementL j) => CxtS h fs a JSAnnotL -> CxtS h fs a JSIdentL -> CxtS h fs a JSAnnotL -> CxtS h fs a (JSCommaList JSIdentL) -> CxtS h fs a JSAnnotL -> CxtS h fs a JSBlockL -> CxtS h fs a JSSemiL -> CxtS h fs a j Source #
iJSIf :: forall h fs a j. ((:-<:) JSStatement fs, InjF fs JSStatementL j) => CxtS h fs a JSAnnotL -> CxtS h fs a JSAnnotL -> CxtS h fs a JSExpressionL -> CxtS h fs a JSAnnotL -> CxtS h fs a JSStatementL -> CxtS h fs a j Source #
iJSIfElse :: forall h fs a j. ((:-<:) JSStatement fs, InjF fs JSStatementL j) => CxtS h fs a JSAnnotL -> CxtS h fs a JSAnnotL -> CxtS h fs a JSExpressionL -> CxtS h fs a JSAnnotL -> CxtS h fs a JSStatementL -> CxtS h fs a JSAnnotL -> CxtS h fs a JSStatementL -> CxtS h fs a j Source #
iJSLabelled :: forall h fs a j. ((:-<:) JSStatement fs, InjF fs JSStatementL j) => CxtS h fs a JSIdentL -> CxtS h fs a JSAnnotL -> CxtS h fs a JSStatementL -> CxtS h fs a j Source #
iJSEmptyStatement :: forall h fs a j. ((:-<:) JSStatement fs, InjF fs JSStatementL j) => CxtS h fs a JSAnnotL -> CxtS h fs a j Source #
iJSExpressionStatement :: forall h fs a j. ((:-<:) JSStatement fs, InjF fs JSStatementL j) => CxtS h fs a JSExpressionL -> CxtS h fs a JSSemiL -> CxtS h fs a j Source #
iJSAssignStatement :: forall h fs a j. ((:-<:) JSStatement fs, InjF fs JSStatementL j) => CxtS h fs a JSExpressionL -> CxtS h fs a JSAssignOpL -> CxtS h fs a JSExpressionL -> CxtS h fs a JSSemiL -> CxtS h fs a j Source #
iJSMethodCall :: forall h fs a j. ((:-<:) JSStatement fs, InjF fs JSStatementL j) => CxtS h fs a JSExpressionL -> CxtS h fs a JSAnnotL -> CxtS h fs a (JSCommaList JSExpressionL) -> CxtS h fs a JSAnnotL -> CxtS h fs a JSSemiL -> CxtS h fs a j Source #
iJSReturn :: forall h fs a j. ((:-<:) JSStatement fs, InjF fs JSStatementL j) => CxtS h fs a JSAnnotL -> CxtS h fs a (Maybe JSExpressionL) -> CxtS h fs a JSSemiL -> CxtS h fs a j Source #
iJSSwitch :: forall h fs a j. ((:-<:) JSStatement fs, InjF fs JSStatementL j) => CxtS h fs a JSAnnotL -> CxtS h fs a JSAnnotL -> CxtS h fs a JSExpressionL -> CxtS h fs a JSAnnotL -> CxtS h fs a JSAnnotL -> CxtS h fs a [JSSwitchPartsL] -> CxtS h fs a JSAnnotL -> CxtS h fs a JSSemiL -> CxtS h fs a j Source #
iJSThrow :: forall h fs a j. ((:-<:) JSStatement fs, InjF fs JSStatementL j) => CxtS h fs a JSAnnotL -> CxtS h fs a JSExpressionL -> CxtS h fs a JSSemiL -> CxtS h fs a j Source #
iJSTry :: forall h fs a j. ((:-<:) JSStatement fs, InjF fs JSStatementL j) => CxtS h fs a JSAnnotL -> CxtS h fs a JSBlockL -> CxtS h fs a [JSTryCatchL] -> CxtS h fs a JSTryFinallyL -> CxtS h fs a j Source #
iJSVariable :: forall h fs a j. ((:-<:) JSStatement fs, InjF fs JSStatementL j) => CxtS h fs a JSAnnotL -> CxtS h fs a (JSCommaList JSExpressionL) -> CxtS h fs a JSSemiL -> CxtS h fs a j Source #
iJSWhile :: forall h fs a j. ((:-<:) JSStatement fs, InjF fs JSStatementL j) => CxtS h fs a JSAnnotL -> CxtS h fs a JSAnnotL -> CxtS h fs a JSExpressionL -> CxtS h fs a JSAnnotL -> CxtS h fs a JSStatementL -> CxtS h fs a j Source #
iJSWith :: forall h fs a j. ((:-<:) JSStatement fs, InjF fs JSStatementL j) => CxtS h fs a JSAnnotL -> CxtS h fs a JSAnnotL -> CxtS h fs a JSExpressionL -> CxtS h fs a JSAnnotL -> CxtS h fs a JSStatementL -> CxtS h fs a JSSemiL -> CxtS h fs a j Source #
iJSCase :: forall h fs a j. ((:-<:) JSSwitchParts fs, InjF fs JSSwitchPartsL j) => CxtS h fs a JSAnnotL -> CxtS h fs a JSExpressionL -> CxtS h fs a JSAnnotL -> CxtS h fs a [JSStatementL] -> CxtS h fs a j Source #
iJSDefault :: forall h fs a j. ((:-<:) JSSwitchParts fs, InjF fs JSSwitchPartsL j) => CxtS h fs a JSAnnotL -> CxtS h fs a JSAnnotL -> CxtS h fs a [JSStatementL] -> CxtS h fs a j Source #
iJSCatch :: forall h fs a j. ((:-<:) JSTryCatch fs, InjF fs JSTryCatchL j) => CxtS h fs a JSAnnotL -> CxtS h fs a JSAnnotL -> CxtS h fs a JSExpressionL -> CxtS h fs a JSAnnotL -> CxtS h fs a JSBlockL -> CxtS h fs a j Source #
iJSCatchIf :: forall h fs a j. ((:-<:) JSTryCatch fs, InjF fs JSTryCatchL j) => CxtS h fs a JSAnnotL -> CxtS h fs a JSAnnotL -> CxtS h fs a JSExpressionL -> CxtS h fs a JSAnnotL -> CxtS h fs a JSExpressionL -> CxtS h fs a JSAnnotL -> CxtS h fs a JSBlockL -> CxtS h fs a j Source #
iJSFinally :: forall h fs a j. ((:-<:) JSTryFinally fs, InjF fs JSTryFinallyL j) => CxtS h fs a JSAnnotL -> CxtS h fs a JSBlockL -> CxtS h fs a j Source #
iJSNoFinally :: forall h fs a j. ((:-<:) JSTryFinally fs, InjF fs JSTryFinallyL j) => CxtS h fs a j Source #
iJSUnaryOpDecr :: forall h fs a j. ((:-<:) JSUnaryOp fs, InjF fs JSUnaryOpL j) => CxtS h fs a JSAnnotL -> CxtS h fs a j Source #
iJSUnaryOpDelete :: forall h fs a j. ((:-<:) JSUnaryOp fs, InjF fs JSUnaryOpL j) => CxtS h fs a JSAnnotL -> CxtS h fs a j Source #
iJSUnaryOpIncr :: forall h fs a j. ((:-<:) JSUnaryOp fs, InjF fs JSUnaryOpL j) => CxtS h fs a JSAnnotL -> CxtS h fs a j Source #
iJSUnaryOpMinus :: forall h fs a j. ((:-<:) JSUnaryOp fs, InjF fs JSUnaryOpL j) => CxtS h fs a JSAnnotL -> CxtS h fs a j Source #
iJSUnaryOpNot :: forall h fs a j. ((:-<:) JSUnaryOp fs, InjF fs JSUnaryOpL j) => CxtS h fs a JSAnnotL -> CxtS h fs a j Source #
iJSUnaryOpPlus :: forall h fs a j. ((:-<:) JSUnaryOp fs, InjF fs JSUnaryOpL j) => CxtS h fs a JSAnnotL -> CxtS h fs a j Source #
iJSUnaryOpTilde :: forall h fs a j. ((:-<:) JSUnaryOp fs, InjF fs JSUnaryOpL j) => CxtS h fs a JSAnnotL -> CxtS h fs a j Source #
iJSUnaryOpTypeof :: forall h fs a j. ((:-<:) JSUnaryOp fs, InjF fs JSUnaryOpL j) => CxtS h fs a JSAnnotL -> CxtS h fs a j Source #
iJSUnaryOpVoid :: forall h fs a j. ((:-<:) JSUnaryOp fs, InjF fs JSUnaryOpL j) => CxtS h fs a JSAnnotL -> CxtS h fs a j Source #
iTokenPn :: forall h fs a j. ((:-<:) TokenPosn fs, InjF fs TokenPosnL j) => Int -> Int -> Int -> CxtS h fs a j Source #
iCommentA :: forall h fs a j. ((:-<:) CommentAnnotation fs, InjF fs CommentAnnotationL j) => CxtS h fs a TokenPosnL -> String -> CxtS h fs a j Source #
iWhiteSpace :: forall h fs a j. ((:-<:) CommentAnnotation fs, InjF fs CommentAnnotationL j) => CxtS h fs a TokenPosnL -> String -> CxtS h fs a j Source #
iNoComment :: forall h fs a j. ((:-<:) CommentAnnotation fs, InjF fs CommentAnnotationL j) => CxtS h fs a j Source #
jsSigNames :: [Name] Source #
Instances
data Ident (e :: * -> *) l where Source #
Instances
data MultiLocalVarDeclCommonAttrsL Source #
Instances
data LocalVarInitL Source #
Instances
data IsOptional Source #
Constructors
Optional | |
NotOptional |
data OptLocalVarInitL Source #
Instances
KDynCase OptLocalVarInit OptLocalVarInitL Source # | |
Defined in Cubix.Language.Parametric.Syntax.VarDecl Methods kdyncase :: forall (e :: Type -> Type) b. OptLocalVarInit e b -> Maybe (b :~: OptLocalVarInitL) # |
data OptLocalVarInit e l where Source #
Constructors
JustLocalVarInit :: e LocalVarInitL -> OptLocalVarInit e OptLocalVarInitL | |
NoLocalVarInit :: OptLocalVarInit e OptLocalVarInitL |
Instances
data LocalVarDeclAttrsL Source #
Instances
KDynCase EmptyLocalVarDeclAttrs LocalVarDeclAttrsL Source # | |
Defined in Cubix.Language.Parametric.Syntax.VarDecl Methods kdyncase :: forall (e :: Type -> Type) b. EmptyLocalVarDeclAttrs e b -> Maybe (b :~: LocalVarDeclAttrsL) # | |
KDynCase ArrayDimVarDeclAttrs LocalVarDeclAttrsL Source # | |
Defined in Cubix.Language.Java.Parametric.Common.Types Methods kdyncase :: forall (e :: Type -> Type) b. ArrayDimVarDeclAttrs e b -> Maybe (b :~: LocalVarDeclAttrsL) # | |
KDynCase CLocalVarAttrs LocalVarDeclAttrsL Source # | |
Defined in Cubix.Language.C.Parametric.Common.Types Methods kdyncase :: forall (e :: Type -> Type) b. CLocalVarAttrs e b -> Maybe (b :~: LocalVarDeclAttrsL) # |
data TupleBinder e l where Source #
Represents declaring a list of identifiers, where the list of identifiers should be thought of a single entity being declared. Not to be used as the LHS of an assignment
This models the (x,y) = (1,2) pattern found in Haskell, or "local x,y" in Lua
Constructors
TupleBinder :: e [IdentL] -> TupleBinder e VarDeclBinderL |
Instances
data IdentIsVarDeclBinder (e :: Type -> Type) i Source #
Constructors
i ~ VarDeclBinderL => IdentIsVarDeclBinder (e IdentL) |
Instances
data EmptyLocalVarDeclAttrs (e :: * -> *) l where Source #
Constructors
EmptyLocalVarDeclAttrs :: EmptyLocalVarDeclAttrs e LocalVarDeclAttrsL |
Instances
data VarDeclBinderL Source #
Instances
data SingleLocalVarDeclL Source #
See MultiLocalVarDecl spec
If no LocalVarInit is present, then the declared variable is unitialized, and may not be referenced until another language If a LocalVarInit is present, then it is executed immediately, before placing the variable in scope, and the result is stored in the declared variable.
We assume this variable can only be referenced by something enclosed by the local block which contains an identifier contained within the var binder, or at least by something assigned to some value derived from such a reference.
This forbids a newly-declared variable from referring to itself (sorry Haskell) This does not model C's "static" keyword
FIXME: So.....I wrote that variables declared without an initializer are unitialized, but that does not model Lua. Luckily, I don't actually depend on this anywhere.
Instances
data SingleLocalVarDecl e l where Source #
Constructors
SingleLocalVarDecl :: e LocalVarDeclAttrsL -> e VarDeclBinderL -> e OptLocalVarInitL -> SingleLocalVarDecl e SingleLocalVarDeclL |
Instances
data EmptyMultiLocalVarDeclCommonAttrs (e :: * -> *) l Source #
Instances
data MultiLocalVarDeclL Source #
Informal spec:
There is a notion of variable scope. Executing a MultiLocalVarDecl statement places each local variable declared into scope. Our intention is that MultiLocalVarDecl is only to be used for local declarations, although we have not yet found a reason why it can't be used for top-level variable declarations as in C.
- - Multi local var decl Each variable declaration has no effect save putting the variable into scope, and executing the initializer expression. Initializer expressions, if present, are executed in left-to-right order. If the language has a notion of an initialized variable, then all declarations for which an initializer is present will be considered initialized.
Executing a MultiLocalVarDecl will execute all contained SingleLocalVardecl
Note: C++ variable declarations cannot use this, because the declarations are effectful FIXME: Does not really give a good account for space allocation (e.g.: references to local variables)
Instances
data MultiLocalVarDecl e l where Source #
Constructors
MultiLocalVarDecl :: e MultiLocalVarDeclCommonAttrsL -> e [SingleLocalVarDeclL] -> MultiLocalVarDecl e MultiLocalVarDeclL |
Instances
See spec for assign
We assume that AssignOpEquals has, as its associated f_op, the function f(x,y)=(typeof x)y where (typeof x)y denotes a type conversion from y to the type of x. We leave it unspecified what exactly that means
Instances
data AssignOpEquals (e :: * -> *) l where Source #
Constructors
AssignOpEquals :: AssignOpEquals e AssignOpL |
Instances
Instances
Instances
The Assign node must have semantics of the following form:
store(lhs',f_op(lhs', eval(rhs))) where lhs' = evalToLoc(lhs)
where eval and evalToLoc are arbitrary evaluation function (potentially with side effects)
The lhs must be evaluated before the rhs.
Note that C can contain arbitrary function calls in lvalues
If an assign may be used in an expression context, then the store takes effect before its return value, all effects in eval(rhs) take effect before the return, and the return value is the value assigned to lhs
If the LHS is a variable, it will be considered initialized after execution of the Assign
FIXME: This spec should maybe contain something like "every var init can be a valid assign", because there are restrictions on assignments, e.g.: C can assign between lvalues with partial overlap. This opens up a rabbit hole of possible constraints we need to specify to avoid allowing transformations to create invalid programs
Instances
data Assign e l where Source #
Instances
data BlockItemL Source #
Instances
Instances
KDynCase EmptyBlockEnd BlockEndL Source # | |
Defined in Cubix.Language.Parametric.Syntax.VarDecl | |
KDynCase LuaBlockEnd BlockEndL Source # | |
Defined in Cubix.Language.Lua.Parametric.Common.Types | |
InjF MLuaSig (Maybe [ExpL]) BlockEndL Source # | |
Defined in Cubix.Language.Lua.Parametric.Common.Types Methods injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a (Maybe [ExpL]) -> CxtS h MLuaSig a BlockEndL Source # projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a BlockEndL -> Maybe (Cxt h (Sum MLuaSig :&: p) a (Maybe [ExpL])) Source # projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a BlockEndL -> Maybe (CxtS h MLuaSig a (Maybe [ExpL])) Source # |
data EmptyBlockEnd (e :: * -> *) l where Source #
Constructors
EmptyBlockEnd :: EmptyBlockEnd e BlockEndL |
Instances
Instances
Block has the following semantics * Any variable introduced by MultiLocalVarDecl may not be referenced outside of the items contained in this block. * Beware that languages such as JavaScript have assignment constructs which do not obey this. We place * no limitation on the visibilty of other kinds of declarations.
We are also using this to model function bodies in Python, though these have the additional restriction of being nonempty
Constructors
Block :: e [BlockItemL] -> e BlockEndL -> Block e BlockL |
Instances
data EmptyBlockItem (e :: * -> *) l where Source #
This is inserted at the end of blocks so that there's a place to insert at the end of blocks, and so that the sort of empty block-item lists can be correctly determined
This is a bit of a hack....but, it's actually kinda nice in some ways
Constructors
EmptyBlockItem :: EmptyBlockItem e BlockItemL |
Instances
pattern JustLocalVarInit' :: (OptLocalVarInit :-<: fs, All HFunctor fs) => CxtS h fs a LocalVarInitL -> CxtS h fs a OptLocalVarInitL Source #
iJustLocalVarInit :: forall h fs a j. ((:-<:) OptLocalVarInit fs, InjF fs OptLocalVarInitL j) => CxtS h fs a LocalVarInitL -> CxtS h fs a j Source #
pattern NoLocalVarInit' :: (OptLocalVarInit :-<: fs, All HFunctor fs) => CxtS h fs a OptLocalVarInitL Source #
iNoLocalVarInit :: forall h fs a j. ((:-<:) OptLocalVarInit fs, InjF fs OptLocalVarInitL j) => CxtS h fs a j Source #
pattern EmptyLocalVarDeclAttrs' :: (EmptyLocalVarDeclAttrs :-<: fs, All HFunctor fs) => CxtS h fs a LocalVarDeclAttrsL Source #
iEmptyLocalVarDeclAttrs :: forall h fs a j. ((:-<:) EmptyLocalVarDeclAttrs fs, InjF fs LocalVarDeclAttrsL j) => CxtS h fs a j Source #
pattern TupleBinder' :: (TupleBinder :-<: fs, All HFunctor fs) => CxtS h fs a [IdentL] -> CxtS h fs a VarDeclBinderL Source #
iTupleBinder :: forall h fs a j. ((:-<:) TupleBinder fs, InjF fs VarDeclBinderL j) => CxtS h fs a [IdentL] -> CxtS h fs a j Source #
pattern IdentIsVarDeclBinder' :: (IdentIsVarDeclBinder :-<: fs, All HFunctor fs) => CxtS h fs a IdentL -> CxtS h fs a VarDeclBinderL Source #
iIdentIsVarDeclBinder :: forall h fs a j. ((:-<:) IdentIsVarDeclBinder fs, InjF fs VarDeclBinderL j) => CxtS h fs a IdentL -> CxtS h fs a j Source #
pattern SingleLocalVarDecl' :: (SingleLocalVarDecl :-<: fs, All HFunctor fs) => CxtS h fs a LocalVarDeclAttrsL -> CxtS h fs a VarDeclBinderL -> CxtS h fs a OptLocalVarInitL -> CxtS h fs a SingleLocalVarDeclL Source #
iSingleLocalVarDecl :: forall h fs a j. ((:-<:) SingleLocalVarDecl fs, InjF fs SingleLocalVarDeclL j) => CxtS h fs a LocalVarDeclAttrsL -> CxtS h fs a VarDeclBinderL -> CxtS h fs a OptLocalVarInitL -> CxtS h fs a j Source #
pattern EmptyMultiLocalVarDeclCommonAttrs' :: (EmptyMultiLocalVarDeclCommonAttrs :-<: fs, All HFunctor fs) => CxtS h fs a MultiLocalVarDeclCommonAttrsL Source #
iEmptyMultiLocalVarDeclCommonAttrs :: forall h fs a j. ((:-<:) EmptyMultiLocalVarDeclCommonAttrs fs, InjF fs MultiLocalVarDeclCommonAttrsL j) => CxtS h fs a j Source #
pattern MultiLocalVarDecl' :: (MultiLocalVarDecl :-<: fs, All HFunctor fs) => CxtS h fs a MultiLocalVarDeclCommonAttrsL -> CxtS h fs a [SingleLocalVarDeclL] -> CxtS h fs a MultiLocalVarDeclL Source #
iMultiLocalVarDecl :: forall h fs a j. ((:-<:) MultiLocalVarDecl fs, InjF fs MultiLocalVarDeclL j) => CxtS h fs a MultiLocalVarDeclCommonAttrsL -> CxtS h fs a [SingleLocalVarDeclL] -> CxtS h fs a j Source #
pattern AssignOpEquals' :: (AssignOpEquals :-<: fs, All HFunctor fs) => CxtS h fs a AssignOpL Source #
iAssignOpEquals :: forall h fs a j. ((:-<:) AssignOpEquals fs, InjF fs AssignOpL j) => CxtS h fs a j Source #
pattern Assign' :: (Assign :-<: fs, All HFunctor fs) => CxtS h fs a LhsL -> CxtS h fs a AssignOpL -> CxtS h fs a RhsL -> CxtS h fs a AssignL Source #
iAssign :: forall h fs a j. ((:-<:) Assign fs, InjF fs AssignL j) => CxtS h fs a LhsL -> CxtS h fs a AssignOpL -> CxtS h fs a RhsL -> CxtS h fs a j Source #
pattern EmptyBlockEnd' :: (EmptyBlockEnd :-<: fs, All HFunctor fs) => CxtS h fs a BlockEndL Source #
iEmptyBlockEnd :: forall h fs a j. ((:-<:) EmptyBlockEnd fs, InjF fs BlockEndL j) => CxtS h fs a j Source #
pattern Block' :: (Block :-<: fs, All HFunctor fs) => CxtS h fs a [BlockItemL] -> CxtS h fs a BlockEndL -> CxtS h fs a BlockL Source #
iBlock :: forall h fs a j. ((:-<:) Block fs, InjF fs BlockL j) => CxtS h fs a [BlockItemL] -> CxtS h fs a BlockEndL -> CxtS h fs a j Source #
pattern EmptyBlockItem' :: (EmptyBlockItem :-<: fs, All HFunctor fs) => CxtS h fs a BlockItemL Source #
iEmptyBlockItem :: forall h fs a j. ((:-<:) EmptyBlockItem fs, InjF fs BlockItemL j) => CxtS h fs a j Source #