License | GPL-2 |
---|---|
Maintainer | yi-devel@googlegroups.com |
Stability | experimental |
Portability | portable |
Safe Haskell | None |
Language | Haskell2010 |
Extensions |
|
Utilities to turn a lexer generated by Alex into a Scanner
that
can be used by Yi. Most lexers will use the types defined here.
Some things are exported for use by lexers themselves through the
use of YiLexerscommon.hsinc
.
- utf8Encode :: Char -> [Word8]
- type Byte = Word8
- type IndexedStr = [(Point, Char)]
- type AlexInput = (Char, [Byte], IndexedStr)
- type Action hlState token = IndexedStr -> hlState -> (hlState, token)
- data AlexState lexerState = AlexState {
- stLexer :: lexerState
- lookedOffset :: !Point
- stPosn :: !Posn
- data Tok t = Tok {}
- tokToSpan :: Tok t -> Span t
- tokFromT :: t -> Tok t
- tokBegin :: Tok t -> Point
- tokEnd :: Tok t -> Point
- data Posn = Posn {}
- startPosn :: Posn
- moveStr :: Posn -> IndexedStr -> Posn
- moveCh :: Posn -> Char -> Posn
- alexGetChar :: AlexInput -> Maybe (Char, AlexInput)
- alexGetByte :: AlexInput -> Maybe (Word8, AlexInput)
- alexCollectChar :: AlexInput -> [Char]
- alexInputPrevChar :: AlexInput -> Char
- actionConst :: token -> Action lexState token
- actionAndModify :: (lexState -> lexState) -> token -> Action lexState token
- actionStringAndModify :: (s -> s) -> (String -> token) -> Action s token
- actionStringConst :: (String -> token) -> Action lexState token
- type ASI s = (AlexState s, AlexInput)
- type TokenLexer l s t i = (l s, i) -> Maybe (t, (l s, i))
- type CharScanner = Scanner Point Char
- data Lexer l s t i = Lexer {
- _step :: TokenLexer l s t i
- _starting :: s -> Point -> Posn -> l s
- _withChars :: Char -> [(Point, Char)] -> i
- _looked :: l s -> Point
- _statePosn :: l s -> Posn
- _lexEmpty :: t
- _startingState :: s
- data StyleLexer l s t i = StyleLexer {
- _tokenToStyle :: t -> StyleName
- _styleLexer :: Lexer l s (Tok t) i
- type StyleLexerASI s t = StyleLexer AlexState s t AlexInput
- commonLexer :: (ASI s -> Maybe (Tok t, ASI s)) -> s -> Lexer AlexState s (Tok t) AlexInput
- lexScanner :: Lexer l s t i -> CharScanner -> Scanner (l s) t
- unfoldLexer :: ((state, input) -> Maybe (token, (state, input))) -> (state, input) -> [(state, token)]
- posnOfsA :: Lens' Posn Point
- posnLineA :: Lens' Posn Int
- posnColA :: Lens' Posn Int
- tokTA :: forall t. Lens' (Tok t) t
- tokPosnA :: forall t. Lens' (Tok t) Posn
- tokLenA :: forall t. Lens' (Tok t) Size
- withChars :: forall l s t i. Lens' (Lexer l s t i) (Char -> [(Point, Char)] -> i)
- step :: forall l s t i. Lens' (Lexer l s t i) (TokenLexer l s t i)
- statePosn :: forall l s t i. Lens' (Lexer l s t i) (l s -> Posn)
- startingState :: forall l s t i. Lens' (Lexer l s t i) s
- starting :: forall l s t i. Lens' (Lexer l s t i) (s -> Point -> Posn -> l s)
- looked :: forall l s t i. Lens' (Lexer l s t i) (l s -> Point)
- lexEmpty :: forall l s t i. Lens' (Lexer l s t i) t
- tokenToStyle :: forall l s t i. Lens' (StyleLexer l s t i) (t -> StyleName)
- styleLexer :: forall l s t i l s i. Lens (StyleLexer l s t i) (StyleLexer l s t i) (Lexer l s (Tok t) i) (Lexer l s (Tok t) i)
- (+~) :: SemiNum absolute relative => absolute -> relative -> absolute
- (~-) :: SemiNum absolute relative => absolute -> absolute -> relative
- newtype Size = Size {}
- type Stroke = Span StyleName
Documentation
utf8Encode :: Char -> [Word8] Source
Encode a Haskell String to a list of Word8 values, in UTF8 format.
type IndexedStr = [(Point, Char)] Source
type AlexInput = (Char, [Byte], IndexedStr) Source
type Action hlState token = IndexedStr -> hlState -> (hlState, token) Source
moveStr :: Posn -> IndexedStr -> Posn Source
alexCollectChar :: AlexInput -> [Char] Source
alexInputPrevChar :: AlexInput -> Char Source
actionConst :: token -> Action lexState token Source
Return a constant token
actionAndModify :: (lexState -> lexState) -> token -> Action lexState token Source
Return a constant token, and modify the lexer state
actionStringAndModify :: (s -> s) -> (String -> token) -> Action s token Source
Convert the parsed string into a token, and also modify the lexer state
actionStringConst :: (String -> token) -> Action lexState token Source
Convert the parsed string into a token
type TokenLexer l s t i = (l s, i) -> Maybe (t, (l s, i)) Source
Function to (possibly) lex a single token and give us the remaining input.
type CharScanner = Scanner Point Char Source
Handy alias
Generalises lexers. This allows us to easily use lexers which
don't want to be cornered into the types we have predefined here
and use in common.hsinc
.
Lexer | |
|
data StyleLexer l s t i Source
StyleLexer | |
|
type StyleLexerASI s t = StyleLexer AlexState s t AlexInput Source
StyleLexer
over ASI
.
commonLexer :: (ASI s -> Maybe (Tok t, ASI s)) -> s -> Lexer AlexState s (Tok t) AlexInput Source
Defines a Lexer
for ASI
. This exists to make using the new
lexScanner
easier if you're using ASI
as all our lexers do
today, 23-08-2014.
lexScanner :: Lexer l s t i -> CharScanner -> Scanner (l s) t Source
Combine a character scanner with a lexer to produce a token
scanner. May be used together with mkHighlighter
to produce a
Highlighter
, or with linearSyntaxMode
to produce a Mode
.
unfoldLexer :: ((state, input) -> Maybe (token, (state, input))) -> (state, input) -> [(state, token)] Source
unfold lexer into a function that returns a stream of (state, token)
Lenses
step :: forall l s t i. Lens' (Lexer l s t i) (TokenLexer l s t i) Source
startingState :: forall l s t i. Lens' (Lexer l s t i) s Source
tokenToStyle :: forall l s t i. Lens' (StyleLexer l s t i) (t -> StyleName) Source
styleLexer :: forall l s t i l s i. Lens (StyleLexer l s t i) (StyleLexer l s t i) (Lexer l s (Tok t) i) (Lexer l s (Tok t) i) Source
Size of a buffer region