yi-language-0.1.0.6: Collection of language-related Yi libraries.

LicenseGPL-2
Maintaineryi-devel@googlegroups.com
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell2010
Extensions
  • TemplateHaskell
  • DisambiguateRecordFields
  • RecordWildCards
  • DeriveFunctor

Yi.Lexer.Alex

Contents

Description

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.

Synopsis

Documentation

utf8Encode :: Char -> [Word8] Source

Encode a Haskell String to a list of Word8 values, in UTF8 format.

type Action hlState token = IndexedStr -> hlState -> (hlState, token) Source

data AlexState lexerState Source

Lexer state

Constructors

AlexState 

Fields

stLexer :: lexerState
 
lookedOffset :: !Point
 
stPosn :: !Posn
 

Instances

Show lexerState => Show (AlexState lexerState) 

data Tok t Source

Constructors

Tok 

Fields

tokT :: t
 
tokLen :: Size
 
tokPosn :: Posn
 

Instances

Functor Tok 
Eq (Tok a) 
Show t => Show (Tok t) 

tokFromT :: t -> Tok t Source

data Posn Source

Constructors

Posn 

Fields

posnOfs :: !Point
 
posnLine :: !Int
 
posnCol :: !Int
 

Instances

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

data Lexer l s t i Source

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.

Constructors

Lexer 

Fields

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

Just like Lexer but also knows how to turn its tokens into StyleNames.

Constructors

StyleLexer 

Fields

_tokenToStyle :: t -> StyleName
 
_styleLexer :: Lexer l s (Tok t) i
 

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

tokTA :: forall t. Lens' (Tok t) t Source

tokPosnA :: forall t. Lens' (Tok t) Posn Source

tokLenA :: forall t. Lens' (Tok t) Size Source

withChars :: forall l s t i. Lens' (Lexer l s t i) (Char -> [(Point, Char)] -> i) Source

step :: forall l s t i. Lens' (Lexer l s t i) (TokenLexer l s t i) Source

statePosn :: forall l s t i. Lens' (Lexer l s t i) (l s -> Posn) Source

startingState :: forall l s t i. Lens' (Lexer l s t i) s Source

starting :: forall l s t i. Lens' (Lexer l s t i) (s -> Point -> Posn -> l s) Source

looked :: forall l s t i. Lens' (Lexer l s t i) (l s -> Point) Source

lexEmpty :: forall l s t i. Lens' (Lexer l s t i) t 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

(+~) :: SemiNum absolute relative => absolute -> relative -> absolute Source

(~-) :: SemiNum absolute relative => absolute -> absolute -> relative Source

newtype Size Source

Size of a buffer region

Constructors

Size 

Fields

fromSize :: Int