yi-0.12.6: The Haskell-Scriptable Editor

LicenseGPL-2
Maintaineryi-devel@googlegroups.com
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell2010
Extensions
  • DeriveDataTypeable
  • DeriveFoldable
  • TypeSynonymInstances
  • FlexibleInstances
  • NondecreasingIndentation

Yi.Syntax.JavaScript

Contents

Description

Parser for the JavaScript language as described at Dogan 2009.

The mode using this parser can be found at Yi.Mode.JavaScript.

Synopsis

Data types, classes and instances

class Strokable a where Source #

Instances of Strokable are datatypes which can be syntax highlighted.

Minimal complete definition

toStrokes

Methods

toStrokes :: a -> Endo [Stroke] Source #

Instances

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

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.

Minimal complete definition

stupid, hasFailed

Methods

stupid :: t -> f t Source #

hasFailed :: f t -> Bool Source #

type BList a = [a] Source #

type Tree t = BList (Statement t) Source #

type Semicolon t = Maybe 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 Source # 

Methods

fold :: Monoid m => Statement m -> m #

foldMap :: Monoid m => (a -> m) -> Statement a -> m #

foldr :: (a -> b -> b) -> b -> Statement a -> b #

foldr' :: (a -> b -> b) -> b -> Statement a -> b #

foldl :: (b -> a -> b) -> b -> Statement a -> b #

foldl' :: (b -> a -> b) -> b -> Statement a -> b #

foldr1 :: (a -> a -> a) -> Statement a -> a #

foldl1 :: (a -> a -> a) -> Statement a -> a #

toList :: Statement a -> [a] #

null :: Statement a -> Bool #

length :: Statement a -> Int #

elem :: Eq a => a -> Statement a -> Bool #

maximum :: Ord a => Statement a -> a #

minimum :: Ord a => Statement a -> a #

sum :: Num a => Statement a -> a #

product :: Num a => Statement a -> a #

IsTree Statement Source # 
Data t => Data (Statement t) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Statement t -> c (Statement t) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Statement t) #

toConstr :: Statement t -> Constr #

dataTypeOf :: Statement t -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (Statement t)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Statement t)) #

gmapT :: (forall b. Data b => b -> b) -> Statement t -> Statement t #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Statement t -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Statement t -> r #

gmapQ :: (forall d. Data d => d -> u) -> Statement t -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Statement t -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Statement t -> m (Statement t) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Statement t -> m (Statement t) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Statement t -> m (Statement t) #

Show t => Show (Statement t) Source # 
Strokable (Statement TT) Source #

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 #

Constructors

Parameters t (BList t) t 
ParErr t 

Instances

Foldable Parameters Source # 

Methods

fold :: Monoid m => Parameters m -> m #

foldMap :: Monoid m => (a -> m) -> Parameters a -> m #

foldr :: (a -> b -> b) -> b -> Parameters a -> b #

foldr' :: (a -> b -> b) -> b -> Parameters a -> b #

foldl :: (b -> a -> b) -> b -> Parameters a -> b #

foldl' :: (b -> a -> b) -> b -> Parameters a -> b #

foldr1 :: (a -> a -> a) -> Parameters a -> a #

foldl1 :: (a -> a -> a) -> Parameters a -> a #

toList :: Parameters a -> [a] #

null :: Parameters a -> Bool #

length :: Parameters a -> Int #

elem :: Eq a => a -> Parameters a -> Bool #

maximum :: Ord a => Parameters a -> a #

minimum :: Ord a => Parameters a -> a #

sum :: Num a => Parameters a -> a #

product :: Num a => Parameters a -> a #

Failable Parameters Source # 
Data t => Data (Parameters t) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Parameters t -> c (Parameters t) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Parameters t) #

toConstr :: Parameters t -> Constr #

dataTypeOf :: Parameters t -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (Parameters t)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Parameters t)) #

gmapT :: (forall b. Data b => b -> b) -> Parameters t -> Parameters t #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Parameters t -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Parameters t -> r #

gmapQ :: (forall d. Data d => d -> u) -> Parameters t -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Parameters t -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Parameters t -> m (Parameters t) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Parameters t -> m (Parameters t) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Parameters t -> m (Parameters t) #

Show t => Show (Parameters t) Source # 
Strokable (Parameters TT) Source # 

data ParExpr t Source #

Constructors

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

Instances

Foldable ParExpr Source # 

Methods

fold :: Monoid m => ParExpr m -> m #

foldMap :: Monoid m => (a -> m) -> ParExpr a -> m #

foldr :: (a -> b -> b) -> b -> ParExpr a -> b #

foldr' :: (a -> b -> b) -> b -> ParExpr a -> b #

foldl :: (b -> a -> b) -> b -> ParExpr a -> b #

foldl' :: (b -> a -> b) -> b -> ParExpr a -> b #

foldr1 :: (a -> a -> a) -> ParExpr a -> a #

foldl1 :: (a -> a -> a) -> ParExpr a -> a #

toList :: ParExpr a -> [a] #

null :: ParExpr a -> Bool #

length :: ParExpr a -> Int #

elem :: Eq a => a -> ParExpr a -> Bool #

maximum :: Ord a => ParExpr a -> a #

minimum :: Ord a => ParExpr a -> a #

sum :: Num a => ParExpr a -> a #

product :: Num a => ParExpr a -> a #

Failable ParExpr Source # 

Methods

stupid :: t -> ParExpr t Source #

hasFailed :: ParExpr t -> Bool Source #

Data t => Data (ParExpr t) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ParExpr t -> c (ParExpr t) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ParExpr t) #

toConstr :: ParExpr t -> Constr #

dataTypeOf :: ParExpr t -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (ParExpr t)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ParExpr t)) #

gmapT :: (forall b. Data b => b -> b) -> ParExpr t -> ParExpr t #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ParExpr t -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ParExpr t -> r #

gmapQ :: (forall d. Data d => d -> u) -> ParExpr t -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ParExpr t -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ParExpr t -> m (ParExpr t) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ParExpr t -> m (ParExpr t) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ParExpr t -> m (ParExpr t) #

Show t => Show (ParExpr t) Source # 

Methods

showsPrec :: Int -> ParExpr t -> ShowS #

show :: ParExpr t -> String #

showList :: [ParExpr t] -> ShowS #

Strokable (ParExpr TT) Source # 

data ForContent t Source #

Constructors

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

Instances

Foldable ForContent Source # 

Methods

fold :: Monoid m => ForContent m -> m #

foldMap :: Monoid m => (a -> m) -> ForContent a -> m #

foldr :: (a -> b -> b) -> b -> ForContent a -> b #

foldr' :: (a -> b -> b) -> b -> ForContent a -> b #

foldl :: (b -> a -> b) -> b -> ForContent a -> b #

foldl' :: (b -> a -> b) -> b -> ForContent a -> b #

foldr1 :: (a -> a -> a) -> ForContent a -> a #

foldl1 :: (a -> a -> a) -> ForContent a -> a #

toList :: ForContent a -> [a] #

null :: ForContent a -> Bool #

length :: ForContent a -> Int #

elem :: Eq a => a -> ForContent a -> Bool #

maximum :: Ord a => ForContent a -> a #

minimum :: Ord a => ForContent a -> a #

sum :: Num a => ForContent a -> a #

product :: Num a => ForContent a -> a #

Failable ForContent Source # 
Data t => Data (ForContent t) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ForContent t -> c (ForContent t) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ForContent t) #

toConstr :: ForContent t -> Constr #

dataTypeOf :: ForContent t -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (ForContent t)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ForContent t)) #

gmapT :: (forall b. Data b => b -> b) -> ForContent t -> ForContent t #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ForContent t -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ForContent t -> r #

gmapQ :: (forall d. Data d => d -> u) -> ForContent t -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ForContent t -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ForContent t -> m (ForContent t) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ForContent t -> m (ForContent t) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ForContent t -> m (ForContent t) #

Show t => Show (ForContent t) Source # 
Strokable (ForContent TT) Source # 

data Block t Source #

Constructors

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

Instances

Foldable Block Source # 

Methods

fold :: Monoid m => Block m -> m #

foldMap :: Monoid m => (a -> m) -> Block a -> m #

foldr :: (a -> b -> b) -> b -> Block a -> b #

foldr' :: (a -> b -> b) -> b -> Block a -> b #

foldl :: (b -> a -> b) -> b -> Block a -> b #

foldl' :: (b -> a -> b) -> b -> Block a -> b #

foldr1 :: (a -> a -> a) -> Block a -> a #

foldl1 :: (a -> a -> a) -> Block a -> a #

toList :: Block a -> [a] #

null :: Block a -> Bool #

length :: Block a -> Int #

elem :: Eq a => a -> Block a -> Bool #

maximum :: Ord a => Block a -> a #

minimum :: Ord a => Block a -> a #

sum :: Num a => Block a -> a #

product :: Num a => Block a -> a #

Failable Block Source # 

Methods

stupid :: t -> Block t Source #

hasFailed :: Block t -> Bool Source #

Data t => Data (Block t) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Block t -> c (Block t) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Block t) #

toConstr :: Block t -> Constr #

dataTypeOf :: Block t -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (Block t)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Block t)) #

gmapT :: (forall b. Data b => b -> b) -> Block t -> Block t #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Block t -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Block t -> r #

gmapQ :: (forall d. Data d => d -> u) -> Block t -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Block t -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Block t -> m (Block t) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Block t -> m (Block t) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Block t -> m (Block t) #

Show t => Show (Block t) Source # 

Methods

showsPrec :: Int -> Block t -> ShowS #

show :: Block t -> String #

showList :: [Block t] -> ShowS #

Strokable (Block TT) Source # 

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 

Instances

Foldable VarDecAss Source # 

Methods

fold :: Monoid m => VarDecAss m -> m #

foldMap :: Monoid m => (a -> m) -> VarDecAss a -> m #

foldr :: (a -> b -> b) -> b -> VarDecAss a -> b #

foldr' :: (a -> b -> b) -> b -> VarDecAss a -> b #

foldl :: (b -> a -> b) -> b -> VarDecAss a -> b #

foldl' :: (b -> a -> b) -> b -> VarDecAss a -> b #

foldr1 :: (a -> a -> a) -> VarDecAss a -> a #

foldl1 :: (a -> a -> a) -> VarDecAss a -> a #

toList :: VarDecAss a -> [a] #

null :: VarDecAss a -> Bool #

length :: VarDecAss a -> Int #

elem :: Eq a => a -> VarDecAss a -> Bool #

maximum :: Ord a => VarDecAss a -> a #

minimum :: Ord a => VarDecAss a -> a #

sum :: Num a => VarDecAss a -> a #

product :: Num a => VarDecAss a -> a #

Failable VarDecAss Source # 
Data t => Data (VarDecAss t) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VarDecAss t -> c (VarDecAss t) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (VarDecAss t) #

toConstr :: VarDecAss t -> Constr #

dataTypeOf :: VarDecAss t -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (VarDecAss t)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (VarDecAss t)) #

gmapT :: (forall b. Data b => b -> b) -> VarDecAss t -> VarDecAss t #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VarDecAss t -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VarDecAss t -> r #

gmapQ :: (forall d. Data d => d -> u) -> VarDecAss t -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VarDecAss t -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VarDecAss t -> m (VarDecAss t) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VarDecAss t -> m (VarDecAss t) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VarDecAss t -> m (VarDecAss t) #

Show t => Show (VarDecAss t) Source # 
Strokable (VarDecAss TT) Source # 

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

Methods

fold :: Monoid m => Expr m -> m #

foldMap :: Monoid m => (a -> m) -> Expr a -> m #

foldr :: (a -> b -> b) -> b -> Expr a -> b #

foldr' :: (a -> b -> b) -> b -> Expr a -> b #

foldl :: (b -> a -> b) -> b -> Expr a -> b #

foldl' :: (b -> a -> b) -> b -> Expr a -> b #

foldr1 :: (a -> a -> a) -> Expr a -> a #

foldl1 :: (a -> a -> a) -> Expr a -> a #

toList :: Expr a -> [a] #

null :: Expr a -> Bool #

length :: Expr a -> Int #

elem :: Eq a => a -> Expr a -> Bool #

maximum :: Ord a => Expr a -> a #

minimum :: Ord a => Expr a -> a #

sum :: Num a => Expr a -> a #

product :: Num a => Expr a -> a #

Failable Expr Source # 

Methods

stupid :: t -> Expr t Source #

hasFailed :: Expr t -> Bool Source #

Data t => Data (Expr t) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Expr t -> c (Expr t) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Expr t) #

toConstr :: Expr t -> Constr #

dataTypeOf :: Expr t -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (Expr t)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Expr t)) #

gmapT :: (forall b. Data b => b -> b) -> Expr t -> Expr t #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Expr t -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Expr t -> r #

gmapQ :: (forall d. Data d => d -> u) -> Expr t -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Expr t -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Expr t -> m (Expr t) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Expr t -> m (Expr t) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Expr t -> m (Expr t) #

Show t => Show (Expr t) Source # 

Methods

showsPrec :: Int -> Expr t -> ShowS #

show :: Expr t -> String #

showList :: [Expr t] -> ShowS #

Strokable (Expr TT) Source # 

data Array t Source #

Constructors

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

Instances

Foldable Array Source # 

Methods

fold :: Monoid m => Array m -> m #

foldMap :: Monoid m => (a -> m) -> Array a -> m #

foldr :: (a -> b -> b) -> b -> Array a -> b #

foldr' :: (a -> b -> b) -> b -> Array a -> b #

foldl :: (b -> a -> b) -> b -> Array a -> b #

foldl' :: (b -> a -> b) -> b -> Array a -> b #

foldr1 :: (a -> a -> a) -> Array a -> a #

foldl1 :: (a -> a -> a) -> Array a -> a #

toList :: Array a -> [a] #

null :: Array a -> Bool #

length :: Array a -> Int #

elem :: Eq a => a -> Array a -> Bool #

maximum :: Ord a => Array a -> a #

minimum :: Ord a => Array a -> a #

sum :: Num a => Array a -> a #

product :: Num a => Array a -> a #

Data t => Data (Array t) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Array t -> c (Array t) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Array t) #

toConstr :: Array t -> Constr #

dataTypeOf :: Array t -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (Array t)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Array t)) #

gmapT :: (forall b. Data b => b -> b) -> Array t -> Array t #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Array t -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Array t -> r #

gmapQ :: (forall d. Data d => d -> u) -> Array t -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Array t -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Array t -> m (Array t) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Array t -> m (Array t) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Array t -> m (Array t) #

Show t => Show (Array t) Source # 

Methods

showsPrec :: Int -> Array t -> ShowS #

show :: Array t -> String #

showList :: [Array t] -> ShowS #

Strokable (Array TT) Source # 

data KeyValue t Source #

Constructors

KeyValue t t (Expr t) 
KeyValueErr t 

Instances

Foldable KeyValue Source # 

Methods

fold :: Monoid m => KeyValue m -> m #

foldMap :: Monoid m => (a -> m) -> KeyValue a -> m #

foldr :: (a -> b -> b) -> b -> KeyValue a -> b #

foldr' :: (a -> b -> b) -> b -> KeyValue a -> b #

foldl :: (b -> a -> b) -> b -> KeyValue a -> b #

foldl' :: (b -> a -> b) -> b -> KeyValue a -> b #

foldr1 :: (a -> a -> a) -> KeyValue a -> a #

foldl1 :: (a -> a -> a) -> KeyValue a -> a #

toList :: KeyValue a -> [a] #

null :: KeyValue a -> Bool #

length :: KeyValue a -> Int #

elem :: Eq a => a -> KeyValue a -> Bool #

maximum :: Ord a => KeyValue a -> a #

minimum :: Ord a => KeyValue a -> a #

sum :: Num a => KeyValue a -> a #

product :: Num a => KeyValue a -> a #

Failable KeyValue Source # 
Data t => Data (KeyValue t) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> KeyValue t -> c (KeyValue t) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (KeyValue t) #

toConstr :: KeyValue t -> Constr #

dataTypeOf :: KeyValue t -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (KeyValue t)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (KeyValue t)) #

gmapT :: (forall b. Data b => b -> b) -> KeyValue t -> KeyValue t #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> KeyValue t -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> KeyValue t -> r #

gmapQ :: (forall d. Data d => d -> u) -> KeyValue t -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> KeyValue t -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> KeyValue t -> m (KeyValue t) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> KeyValue t -> m (KeyValue t) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> KeyValue t -> m (KeyValue t) #

Show t => Show (KeyValue t) Source # 

Methods

showsPrec :: Int -> KeyValue t -> ShowS #

show :: KeyValue t -> String #

showList :: [KeyValue t] -> ShowS #

Strokable (KeyValue TT) Source # 

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.