yi-0.6.2.3: The Haskell-Scriptable EditorSource codeContentsIndex
Yi.Syntax.JavaScript
Contents
Data types, classes and instances
Helper functions.
Stroking functions
The parser
Parsing helpers
Simple parsers
Recovery parsers
Utility stuff
Synopsis
class Strokable a where
toStrokes :: a -> Endo [Stroke]
class Failable f where
stupid :: t -> f t
hasFailed :: f t -> Bool
type BList a = [a]
type Tree t = BList (Statement t)
type Semicolon t = Maybe t
data Statement t
= FunDecl t t (Parameters t) (Block t)
| VarDecl t (BList (VarDecAss t)) (Semicolon t)
| Return t (Maybe (Expr t)) (Semicolon t)
| While t (ParExpr t) (Block t)
| DoWhile t (Block t) t (ParExpr t) (Semicolon t)
| For t t (Expr t) (ForContent t) t (Block t)
| If t (ParExpr t) (Block t) (Maybe (Statement t))
| Else t (Block t)
| With t (ParExpr t) (Block t)
| Comm t
| Expr (Expr t) (Semicolon t)
data Parameters t
= Parameters t (BList t) t
| ParErr t
data ParExpr t
= ParExpr t (BList (Expr t)) t
| ParExprErr t
data ForContent t
= ForNormal t (Expr t) t (Expr t)
| ForIn t (Expr t)
| ForErr t
data Block t
= Block t (BList (Statement t)) t
| BlockOne (Statement t)
| BlockErr t
data VarDecAss t
= AssBeg t (Maybe (VarDecAss t))
| AssRst t (Expr t)
| AssErr t
data Expr t
= ExprObj t (BList (KeyValue t)) t
| ExprPrefix t (Expr t)
| ExprNew t (Expr t)
| ExprSimple t (Maybe (Expr t))
| ExprParen t (Expr t) t (Maybe (Expr t))
| ExprAnonFun t (Parameters t) (Block t)
| ExprTypeOf t (Expr t)
| ExprFunCall t (ParExpr t) (Maybe (Expr t))
| OpExpr t (Expr t)
| ExprCond t (Expr t) t (Expr t)
| ExprArr t (Maybe (Array t)) t (Maybe (Expr t))
| PostExpr t
| ExprErr t
data Array t
= ArrCont (Expr t) (Maybe (Array t))
| ArrRest t (Array t) (Maybe (Array t))
| ArrErr t
data KeyValue t
= KeyValue t t (Expr t)
| KeyValueErr t
normal :: TT -> Endo [Stroke]
error :: TT -> Endo [Stroke]
one :: (t -> a) -> t -> Endo [a]
modStroke :: StyleName -> Stroke -> Stroke
nError :: [TT] -> [TT] -> Endo [Stroke]
failStroker :: [TT] -> TT -> Endo [Stroke]
tokenToStroke :: TT -> Stroke
getStrokes :: Tree TT -> Point -> Point -> Point -> [Stroke]
parse :: P TT (Tree TT)
statement :: P TT (Statement TT)
block :: P TT (Block TT)
stmtExpr :: P TT (Expr TT)
opExpr :: P TT (Expr TT)
expression :: P TT (Expr TT)
array :: P TT (Expr TT)
semicolon :: P TT (Maybe TT)
parameters :: P TT (Parameters TT)
parExpr :: P TT (ParExpr TT)
comment :: P TT TT
preOp :: P TT TT
inOp :: P TT TT
postOp :: P TT TT
opTok :: P TT TT
simpleTok :: P TT TT
strTok :: P TT TT
numTok :: P TT TT
name :: P TT TT
boolean :: P TT TT
res :: Reserved -> P TT TT
spc :: Char -> P TT TT
oper :: Operator -> P TT TT
plzTok :: P TT TT -> P TT TT
plzSpc :: Char -> P TT TT
plzExpr :: P TT (Expr TT)
plz :: Failable f => P TT (f TT) -> P TT (f TT)
anything :: P s TT
hate :: Int -> P s a -> P s a
fromBlock :: Block t -> [Statement t]
firstTok :: Foldable f => f t -> t
errorToken :: TT
isError :: TT -> Bool
toTT :: t -> Tok t
fromTT :: Tok t -> t
Data types, classes and instances
class Strokable a whereSource
Instances of Strokable are datatypes which can be syntax highlighted.
Methods
toStrokes :: a -> Endo [Stroke]Source
show/hide Instances
class Failable f whereSource
Instances of Failable can represent failure. This is a useful class for future work, since then we can make stroking much easier.
Methods
stupid :: t -> f tSource
hasFailed :: f t -> BoolSource
show/hide Instances
type BList a = [a]Source
type Tree t = BList (Statement t)Source
type Semicolon t = Maybe tSource
data Statement t Source
Constructors
FunDecl t t (Parameters t) (Block t)
VarDecl t (BList (VarDecAss t)) (Semicolon t)
Return t (Maybe (Expr t)) (Semicolon t)
While t (ParExpr t) (Block t)
DoWhile t (Block t) t (ParExpr t) (Semicolon t)
For t t (Expr t) (ForContent t) t (Block t)
If t (ParExpr t) (Block t) (Maybe (Statement t))
Else t (Block t)
With t (ParExpr t) (Block t)
Comm t
Expr (Expr t) (Semicolon t)
show/hide Instances
data Parameters t Source
Constructors
Parameters t (BList t) t
ParErr t
show/hide Instances
data ParExpr t Source
Constructors
ParExpr t (BList (Expr t)) t
ParExprErr t
show/hide Instances
data ForContent t Source
Constructors
ForNormal t (Expr t) t (Expr t)
ForIn t (Expr t)
ForErr t
show/hide Instances
data Block t Source
Constructors
Block t (BList (Statement t)) t
BlockOne (Statement t)
BlockErr t
show/hide Instances
data VarDecAss t Source
Represents either a variable name or a variable name assigned to an expression. AssBeg is a variable name maybe followed by an assignment. AssRst is an equals sign and an expression. (AssBeg x (Just (AssRst '=' '5'))) means x = 5.
Constructors
AssBeg t (Maybe (VarDecAss t))
AssRst t (Expr t)
AssErr t
show/hide Instances
data Expr t Source
Constructors
ExprObj t (BList (KeyValue t)) t
ExprPrefix t (Expr t)
ExprNew t (Expr t)
ExprSimple t (Maybe (Expr t))
ExprParen t (Expr t) t (Maybe (Expr t))
ExprAnonFun t (Parameters t) (Block t)
ExprTypeOf t (Expr t)
ExprFunCall t (ParExpr t) (Maybe (Expr t))
OpExpr t (Expr t)
ExprCond t (Expr t) t (Expr t)
ExprArr t (Maybe (Array t)) t (Maybe (Expr t))
PostExpr t
ExprErr t
show/hide Instances
data Array t Source
Constructors
ArrCont (Expr t) (Maybe (Array t))
ArrRest t (Array t) (Maybe (Array t))
ArrErr t
show/hide Instances
data KeyValue t Source
Constructors
KeyValue t t (Expr t)
KeyValueErr t
show/hide Instances
Helper functions.
normal :: TT -> Endo [Stroke]Source
Normal stroker.
error :: TT -> Endo [Stroke]Source
Error stroker.
one :: (t -> a) -> t -> Endo [a]Source
modStroke :: StyleName -> Stroke -> StrokeSource
Given a new style and a stroke, return a stroke with the new style appended to the old one.
Stroking functions
nError :: [TT] -> [TT] -> Endo [Stroke]Source
Given a list of tokens to check for errors (xs) and a list of tokens to stroke (xs'), returns normal strokes for xs' if there were no errors. Otherwise returns error strokes for xs'.
failStroker :: [TT] -> TT -> Endo [Stroke]Source
Given a list of TT, if any of them is an error, returns an error stroker, otherwise a normal stroker. Using e.g. existentials, we could make this more general and have support for heterogeneous lists of elements which implement Failable, but I haven't had the time to fix this.
tokenToStroke :: TT -> StrokeSource
Given a TT, return a Stroke for it.
getStrokes :: Tree TT -> Point -> Point -> Point -> [Stroke]Source
The main stroking function.
The parser
parse :: P TT (Tree TT)Source
Main parser.
statement :: P TT (Statement TT)Source
Parser for statements such as return, while, do-while, for, etc.
block :: P TT (Block TT)Source

Parser for blocks, i.e. a bunch of statements wrapped in curly brackets or just a single statement.

Note that this works for JavaScript 1.8 lambda style function bodies as well, e.g. function hello() 5, since expressions are also statements and we don't require a trailing semi-colon.

TODO: function hello() var x; is not a valid program.

stmtExpr :: P TT (Expr TT)Source
Parser for expressions which may be statements. In reality, any expression is also a valid statement, but this is a slight compromise to get rid of the massive performance loss which is introduced when allowing JavaScript objects to be valid statements.
opExpr :: P TT (Expr TT)Source
The basic idea here is to parse the rest of expressions, e.g. + 3 in x + 3 or [i] in x[i]. Anything which is useful in such a scenario goes here. TODO: This accepts [], but shouldn't, since x[] is invalid.
expression :: P TT (Expr TT)Source
Parser for expressions.
array :: P TT (Expr TT)Source
Parses both empty and non-empty arrays. Should probably be split up into further parts to allow for the separation of [] and [1, 2, 3].
Parsing helpers
semicolon :: P TT (Maybe TT)Source
Parses a semicolon if it's there.
parameters :: P TT (Parameters TT)Source
Parses a comma-separated list of valid identifiers.
parExpr :: P TT (ParExpr TT)Source
Simple parsers
comment :: P TT TTSource
Parses a comment.
preOp :: P TT TTSource
Parses a prefix operator.
inOp :: P TT TTSource
Parses a infix operator.
postOp :: P TT TTSource
Parses a postfix operator.
opTok :: P TT TTSource
Parses any literal.
simpleTok :: P TT TTSource
Parses any literal.
strTok :: P TT TTSource
Parses any string.
numTok :: P TT TTSource
Parses any valid number.
name :: P TT TTSource
Parses any valid identifier.
boolean :: P TT TTSource
Parses any boolean.
res :: Reserved -> P TT TTSource
Parses a reserved word.
spc :: Char -> P TT TTSource
Parses a special token.
oper :: Operator -> P TT TTSource
Parses an operator.
Recovery parsers
plzTok :: P TT TT -> P TT TTSource
Expects a token x, recovers with errorToken.
plzSpc :: Char -> P TT TTSource
Expects a special token.
plzExpr :: P TT (Expr TT)Source
Expects an expression.
plz :: Failable f => P TT (f TT) -> P TT (f TT)Source
anything :: P s TTSource
General recovery parser, inserts an error token.
hate :: Int -> P s a -> P s aSource
Weighted recovery.
Utility stuff
fromBlock :: Block t -> [Statement t]Source
firstTok :: Foldable f => f t -> tSource
errorToken :: TTSource
isError :: TT -> BoolSource
toTT :: t -> Tok tSource
Better name for tokFromT.
fromTT :: Tok t -> tSource
Better name for tokT.
Produced by Haddock version 2.6.1