yi-0.8.1: The Haskell-Scriptable Editor

Safe HaskellNone
LanguageHaskell2010

Yi.Syntax.JavaScript

Contents

Synopsis

Data types, classes and instances

class Strokable a where Source

Instances of Strokable are datatypes which can be syntax highlighted.

Methods

toStrokes :: a -> Endo [Stroke] Source

Instances

Strokable (Tok Token) 
Strokable (KeyValue TT) 
Strokable (Array TT) 
Strokable (Expr TT) 
Strokable (VarDecAss TT) 
Strokable (Block TT) 
Strokable (ForContent TT) 
Strokable (ParExpr TT) 
Strokable (Parameters TT) 
Strokable (Statement TT)

TODO: This code is *screaming* for some generic programming.

TODO: Somehow fix Failable and failStroker to be more "generic". This will make these instances much nicer and we won't have to make ad-hoc stuff like this.

class Failable f where Source

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 t Source

hasFailed :: f t -> Bool Source

type BList a = [a] Source

type Tree t = BList (Statement t) Source

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) 

Instances

Foldable Statement 
IsTree Statement 
Data t => Data (Statement t) 
Show t => Show (Statement t) 
Strokable (Statement TT)

TODO: This code is *screaming* for some generic programming.

TODO: Somehow fix Failable and failStroker to be more "generic". This will make these instances much nicer and we won't have to make ad-hoc stuff like this.

Typeable (* -> *) Statement 

data ParExpr t Source

Constructors

ParExpr t (BList (Expr t)) t 
ParExprErr t 

data ForContent t Source

Constructors

ForNormal t (Expr t) t (Expr t) 
ForIn t (Expr t) 
ForErr t 

data Block t Source

Constructors

Block t (BList (Statement t)) t 
BlockOne (Statement t) 
BlockErr t 

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 

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 

Instances

Foldable Expr 
Failable Expr 
Data t => Data (Expr t) 
Show t => Show (Expr t) 
Strokable (Expr TT) 
Typeable (* -> *) Expr 

data Array t Source

Constructors

ArrCont (Expr t) (Maybe (Array t)) 
ArrRest t (Array t) (Maybe (Array t)) 
ArrErr t 

Instances

Foldable Array 
Data t => Data (Array t) 
Show t => Show (Array t) 
Strokable (Array TT) 
Typeable (* -> *) Array 

data KeyValue t Source

Constructors

KeyValue t t (Expr t) 
KeyValueErr t 

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 -> Stroke Source

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 -> Stroke Source

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.

Simple parsers

comment :: P TT TT Source

Parses a comment.

preOp :: P TT TT Source

Parses a prefix operator.

inOp :: P TT TT Source

Parses a infix operator.

postOp :: P TT TT Source

Parses a postfix operator.

opTok :: P TT TT Source

Parses any literal.

simpleTok :: P TT TT Source

Parses any literal.

strTok :: P TT TT Source

Parses any string.

numTok :: P TT TT Source

Parses any valid number.

name :: P TT TT Source

Parses any valid identifier.

boolean :: P TT TT Source

Parses any boolean.

res :: Reserved -> P TT TT Source

Parses a reserved word.

spc :: Char -> P TT TT Source

Parses a special token.

oper :: Operator -> P TT TT Source

Parses an operator.

Recovery parsers

plzTok :: P TT TT -> P TT TT Source

Expects a token x, recovers with errorToken.

plzSpc :: Char -> P TT TT Source

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 TT Source

General recovery parser, inserts an error token.

hate :: Int -> P s a -> P s a Source

Weighted recovery.

Utility stuff

firstTok :: Foldable f => f t -> t Source

toTT :: t -> Tok t Source

Better name for tokFromT.

fromTT :: Tok t -> t Source

Better name for tokT.