yi-0.6.2.3: The Haskell-Scriptable EditorSource codeContentsIndex
Yi.Syntax
Description
This module defines a common interface for syntax-awareness.
Synopsis
data Highlighter cache syntax = SynHL {
hlStartState :: cache
hlRun :: Scanner Point Char -> Point -> cache -> cache
hlGetTree :: cache -> Int -> syntax
hlFocus :: Map Int Region -> cache -> cache
}
data Cache state result
data Scanner st a = Scanner {
scanInit :: st
scanLooked :: st -> Point
scanEmpty :: a
scanRun :: st -> [(st, a)]
}
data ExtHL syntax = forall cache . ExtHL (Highlighter cache syntax)
noHighlighter :: Highlighter () syntax
mkHighlighter :: forall state result. Show state => (Scanner Point Char -> Scanner state result) -> Highlighter (Cache state result) result
skipScanner :: Int -> Scanner st a -> Scanner st a
emptyFileScan :: Scanner Point Char
newtype Point = Point {
fromPoint :: Int
}
newtype Size = Size {
fromSize :: Int
}
type Length = Int
type Stroke = Span StyleName
data Span a = Span {
spanBegin :: !Point
spanContents :: !a
spanEnd :: !Point
}
Documentation
data Highlighter cache syntax Source
The main type of syntax highlighters. This record type combines all the required functions, and is parametrized on the type of the internal state.
Constructors
SynHL
hlStartState :: cacheThe start state for the highlighter.
hlRun :: Scanner Point Char -> Point -> cache -> cache
hlGetTree :: cache -> Int -> syntax
hlFocus :: Map Int Region -> cache -> cachefocus at a given point, and return the coresponding node. (hint -- the root can always be returned, at the cost of performance.)
data Cache state result Source
data Scanner st a Source
Constructors
Scanner
scanInit :: stInitial state
scanLooked :: st -> PointHow far did the scanner look to produce this intermediate state? The state can be reused as long as nothing changes before that point.
scanEmpty :: a
scanRun :: st -> [(st, a)]Running function returns a list of results and intermediate states. Note: the state is the state before producing the result in the second component.
show/hide Instances
data ExtHL syntax Source
Constructors
forall cache . ExtHL (Highlighter cache syntax)
noHighlighter :: Highlighter () syntaxSource
mkHighlighter :: forall state result. Show state => (Scanner Point Char -> Scanner state result) -> Highlighter (Cache state result) resultSource
This takes as input a scanner that returns the full result at each element in the list; perhaps in a different form for the purpose of incremental-lazy eval.
skipScanner :: Int -> Scanner st a -> Scanner st aSource
emptyFileScan :: Scanner Point CharSource
newtype Point Source
A point in a buffer
Constructors
Point
fromPoint :: Int
show/hide Instances
newtype Size Source
Size of a buffer region
Constructors
Size
fromSize :: Int
show/hide Instances
type Length = IntSource
type Stroke = Span StyleNameSource
data Span a Source
Constructors
Span
spanBegin :: !Point
spanContents :: !a
spanEnd :: !Point
show/hide Instances
Produced by Haddock version 2.6.1