yi-0.6.2.3: The Haskell-Scriptable EditorSource codeContentsIndex
Yi.Lexer.Alex
Contents
Names expected by Alex code
Other things closely associated with the lexer
Lexer actions
Data produced by the scanner
Description
Utilities to turn a lexer generated by Alex into a scanner that can be used by Yi.
Synopsis
type AlexInput = (Char, IndexedStr)
alexGetChar :: AlexInput -> Maybe (Char, AlexInput)
alexInputPrevChar :: AlexInput -> Char
data AlexState lexerState = AlexState {
stLexer :: lexerState
lookedOffset :: !Point
stPosn :: !Posn
}
unfoldLexer :: ((AlexState lexState, input) -> Maybe (token, (AlexState lexState, input))) -> (AlexState lexState, input) -> [(AlexState lexState, token)]
lexScanner :: forall lexerState token. ((AlexState lexerState, AlexInput) -> Maybe (token, (AlexState lexerState, AlexInput))) -> lexerState -> Scanner Point Char -> Scanner (AlexState lexerState) token
alexCollectChar :: AlexInput -> [Char]
actionConst :: token -> Action lexState token
actionAndModify :: (lexState -> lexState) -> token -> Action lexState token
actionStringAndModify :: (lexState -> lexState) -> (String -> token) -> Action lexState token
actionStringConst :: (String -> token) -> Action lexState token
data Tok t = Tok {
tokT :: t
tokLen :: Size
tokPosn :: Posn
}
tokBegin :: forall t. Tok t -> Point
tokEnd :: forall t. Tok t -> Point
tokFromT :: forall t. t -> Tok t
tokRegion :: Tok t -> Region
data Posn = Posn {
posnOfs :: !Point
posnLine :: !Int
posnCol :: !Int
}
startPosn :: Posn
moveStr :: Posn -> IndexedStr -> Posn
type ASI s = (AlexState s, AlexInput)
(+~) :: SemiNum absolute relative => absolute -> relative -> absolute
(~-) :: SemiNum absolute relative => absolute -> absolute -> relative
newtype Size = Size {
fromSize :: Int
}
type Stroke = Span StyleName
tokToSpan :: Tok t -> Span t
Names expected by Alex code
type AlexInput = (Char, IndexedStr)Source
alexGetChar :: AlexInput -> Maybe (Char, AlexInput)Source
alexInputPrevChar :: AlexInput -> CharSource
Other things closely associated with the lexer
data AlexState lexerState Source
Lexer state
Constructors
AlexState
stLexer :: lexerState
lookedOffset :: !Point
stPosn :: !Posn
show/hide Instances
Show lexerState => Show (AlexState lexerState)
unfoldLexer :: ((AlexState lexState, input) -> Maybe (token, (AlexState lexState, input))) -> (AlexState lexState, input) -> [(AlexState lexState, token)]Source
unfold lexer function into a function that returns a stream of (state x token)
lexScannerSource
:: forall lexerState token .
=> (AlexState lexerState, AlexInput) -> Maybe (token, (AlexState lexerState, AlexInput))A lexer
-> lexerStateInitial user state for the lexer
-> Scanner Point Char
-> Scanner (AlexState lexerState) token
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.
alexCollectChar :: AlexInput -> [Char]Source
Lexer actions
actionConst :: token -> Action lexState tokenSource
Return a constant token
actionAndModify :: (lexState -> lexState) -> token -> Action lexState tokenSource
Return a constant token, and modify the lexer state
actionStringAndModify :: (lexState -> lexState) -> (String -> token) -> Action lexState tokenSource
Convert the parsed string into a token, and also modify the lexer state
actionStringConst :: (String -> token) -> Action lexState tokenSource
Convert the parsed string into a token
Data produced by the scanner
data Tok t Source
Constructors
Tok
tokT :: t
tokLen :: Size
tokPosn :: Posn
show/hide Instances
tokBegin :: forall t. Tok t -> PointSource
tokEnd :: forall t. Tok t -> PointSource
tokFromT :: forall t. t -> Tok tSource
tokRegion :: Tok t -> RegionSource
data Posn Source
Constructors
Posn
posnOfs :: !Point
posnLine :: !Int
posnCol :: !Int
show/hide Instances
startPosn :: PosnSource
moveStr :: Posn -> IndexedStr -> PosnSource
type ASI s = (AlexState s, AlexInput)Source
(+~) :: SemiNum absolute relative => absolute -> relative -> absoluteSource
(~-) :: SemiNum absolute relative => absolute -> absolute -> relativeSource
newtype Size Source
Size of a buffer region
Constructors
Size
fromSize :: Int
show/hide Instances
type Stroke = Span StyleNameSource
tokToSpan :: Tok t -> Span tSource
Produced by Haddock version 2.6.1