Safe Haskell | None |
---|
- class Strokable a where
- class Failable f where
- 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
- data Block t
- data VarDecAss 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
- 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
Instances of Strokable
are datatypes which can be syntax highlighted.
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. |
Instances of Failable
can represent failure. This is a useful class for
future work, since then we can make stroking much easier.
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) |
Typeable1 Statement | |
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. |
data Parameters t Source
Parameters t (BList t) t | |
ParErr t |
Typeable1 Parameters | |
Foldable Parameters | |
Failable Parameters | |
Data t => Data (Parameters t) | |
Show t => Show (Parameters t) | |
Strokable (Parameters TT) |
ParExpr t (BList (Expr t)) t | |
ParExprErr t |
data ForContent t Source
Typeable1 ForContent | |
Foldable ForContent | |
Failable ForContent | |
Data t => Data (ForContent t) | |
Show t => Show (ForContent t) | |
Strokable (ForContent TT) |
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
means x
(Just (AssRst
'=' '5')))x = 5
.
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 |
KeyValue t t (Expr t) | |
KeyValueErr t |
Helper functions.
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.
The parser
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.
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
parameters :: P TT (Parameters TT)Source
Parses a comma-separated list of valid identifiers.