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

LicenseGPL-2
Maintaineryi-devel@googlegroups.com
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell2010
Extensions
  • TemplateHaskell
  • TemplateHaskellQuotes
  • 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

Instances

Show lexerState => Show (AlexState lexerState) Source # 

Methods

showsPrec :: Int -> AlexState lexerState -> ShowS #

show :: AlexState lexerState -> String #

showList :: [AlexState lexerState] -> ShowS #

data Tok t Source #

Constructors

Tok 

Fields

Instances

Functor Tok Source # 

Methods

fmap :: (a -> b) -> Tok a -> Tok b #

(<$) :: a -> Tok b -> Tok a #

Eq (Tok a) Source # 

Methods

(==) :: Tok a -> Tok a -> Bool #

(/=) :: Tok a -> Tok a -> Bool #

Show t => Show (Tok t) Source # 

Methods

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

show :: Tok t -> String #

showList :: [Tok t] -> ShowS #

tokFromT :: t -> Tok t Source #

data Posn Source #

Constructors

Posn 

Fields

Instances

Eq Posn Source # 

Methods

(==) :: Posn -> Posn -> Bool #

(/=) :: Posn -> Posn -> Bool #

Ord Posn Source # 

Methods

compare :: Posn -> Posn -> Ordering #

(<) :: Posn -> Posn -> Bool #

(<=) :: Posn -> Posn -> Bool #

(>) :: Posn -> Posn -> Bool #

(>=) :: Posn -> Posn -> Bool #

max :: Posn -> Posn -> Posn #

min :: Posn -> Posn -> Posn #

Show Posn Source # 

Methods

showsPrec :: Int -> Posn -> ShowS #

show :: Posn -> String #

showList :: [Posn] -> ShowS #

Ix Posn Source # 

Methods

range :: (Posn, Posn) -> [Posn] #

index :: (Posn, Posn) -> Posn -> Int #

unsafeIndex :: (Posn, Posn) -> Posn -> Int

inRange :: (Posn, Posn) -> Posn -> Bool #

rangeSize :: (Posn, Posn) -> Int #

unsafeRangeSize :: (Posn, Posn) -> Int

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

data StyleLexer l s t i Source #

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

Constructors

StyleLexer 

Fields

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 t. Lens (Tok t) (Tok t) 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

Instances

Enum Size Source # 

Methods

succ :: Size -> Size #

pred :: Size -> Size #

toEnum :: Int -> Size #

fromEnum :: Size -> Int #

enumFrom :: Size -> [Size] #

enumFromThen :: Size -> Size -> [Size] #

enumFromTo :: Size -> Size -> [Size] #

enumFromThenTo :: Size -> Size -> Size -> [Size] #

Eq Size Source # 

Methods

(==) :: Size -> Size -> Bool #

(/=) :: Size -> Size -> Bool #

Integral Size Source # 

Methods

quot :: Size -> Size -> Size #

rem :: Size -> Size -> Size #

div :: Size -> Size -> Size #

mod :: Size -> Size -> Size #

quotRem :: Size -> Size -> (Size, Size) #

divMod :: Size -> Size -> (Size, Size) #

toInteger :: Size -> Integer #

Num Size Source # 

Methods

(+) :: Size -> Size -> Size #

(-) :: Size -> Size -> Size #

(*) :: Size -> Size -> Size #

negate :: Size -> Size #

abs :: Size -> Size #

signum :: Size -> Size #

fromInteger :: Integer -> Size #

Ord Size Source # 

Methods

compare :: Size -> Size -> Ordering #

(<) :: Size -> Size -> Bool #

(<=) :: Size -> Size -> Bool #

(>) :: Size -> Size -> Bool #

(>=) :: Size -> Size -> Bool #

max :: Size -> Size -> Size #

min :: Size -> Size -> Size #

Real Size Source # 

Methods

toRational :: Size -> Rational #

Show Size Source # 

Methods

showsPrec :: Int -> Size -> ShowS #

show :: Size -> String #

showList :: [Size] -> ShowS #

Binary Size Source # 

Methods

put :: Size -> Put #

get :: Get Size #

putList :: [Size] -> Put #

SemiNum Point Size Source #