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

Copyright(c) Don Stewart 2007
LicenseGPL-2
Maintaineryi-devel@googlegroups.com
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell2010
Extensions
  • ScopedTypeVariables
  • DeriveFunctor
  • DeriveTraversable
  • DeriveFoldable
  • ExistentialQuantification
  • ExplicitForAll

Yi.Syntax

Description

This module defines a common interface for syntax-awareness.

There have been many tens of wasted hours in this and lexer modules. This note is to commemorate those who have fallen in battle.

Synopsis

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 

Fields

data Cache state result Source #

data Scanner st a Source #

Constructors

Scanner 

Fields

  • scanInit :: st

    Initial state

  • scanLooked :: st -> Point

    How 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.

Instances

Functor (Scanner st) Source # 

Methods

fmap :: (a -> b) -> Scanner st a -> Scanner st b #

(<$) :: a -> Scanner st b -> Scanner st a #

data ExtHL syntax Source #

Constructors

ExtHL (Highlighter cache syntax) 

mkHighlighter :: forall state result. Show state => (Scanner Point Char -> Scanner state result) -> Highlighter (Cache state result) result Source #

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 a Source #

newtype Point Source #

A point in a buffer

Constructors

Point 

Fields

Instances

Bounded Point Source # 
Enum Point Source # 
Eq Point Source # 

Methods

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

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

Integral Point Source # 
Num Point Source # 
Ord Point Source # 

Methods

compare :: Point -> Point -> Ordering #

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

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

(>) :: Point -> Point -> Bool #

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

max :: Point -> Point -> Point #

min :: Point -> Point -> Point #

Real Point Source # 

Methods

toRational :: Point -> Rational #

Show Point Source # 

Methods

showsPrec :: Int -> Point -> ShowS #

show :: Point -> String #

showList :: [Point] -> ShowS #

Ix Point Source # 
Binary Point Source # 

Methods

put :: Point -> Put #

get :: Get Point #

putList :: [Point] -> Put #

SemiNum Point Size 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 # 

data Span a Source #

Constructors

Span 

Fields

Instances

Functor Span Source # 

Methods

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

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

Foldable Span Source # 

Methods

fold :: Monoid m => Span m -> m #

foldMap :: Monoid m => (a -> m) -> Span a -> m #

foldr :: (a -> b -> b) -> b -> Span a -> b #

foldr' :: (a -> b -> b) -> b -> Span a -> b #

foldl :: (b -> a -> b) -> b -> Span a -> b #

foldl' :: (b -> a -> b) -> b -> Span a -> b #

foldr1 :: (a -> a -> a) -> Span a -> a #

foldl1 :: (a -> a -> a) -> Span a -> a #

toList :: Span a -> [a] #

null :: Span a -> Bool #

length :: Span a -> Int #

elem :: Eq a => a -> Span a -> Bool #

maximum :: Ord a => Span a -> a #

minimum :: Ord a => Span a -> a #

sum :: Num a => Span a -> a #

product :: Num a => Span a -> a #

Traversable Span Source # 

Methods

traverse :: Applicative f => (a -> f b) -> Span a -> f (Span b) #

sequenceA :: Applicative f => Span (f a) -> f (Span a) #

mapM :: Monad m => (a -> m b) -> Span a -> m (Span b) #

sequence :: Monad m => Span (m a) -> m (Span a) #

Show a => Show (Span a) Source # 

Methods

showsPrec :: Int -> Span a -> ShowS #

show :: Span a -> String #

showList :: [Span a] -> ShowS #