yi-core-0.15.0: Yi editor core library

LicenseGPL-2
Maintaineryi-devel@googlegroups.com
Stabilityexperimental
Portabilityportable
Safe HaskellSafe
LanguageHaskell2010
Extensions
  • UndecidableInstances
  • MonoLocalBinds
  • ScopedTypeVariables
  • OverloadedStrings
  • GADTs
  • GADTSyntax
  • TypeSynonymInstances
  • FlexibleInstances
  • ConstrainedClassMethods
  • MultiParamTypeClasses
  • FunctionalDependencies
  • ExplicitForAll

Yi.Interact

Description

This is a library of interactive processes combinators, usable to define extensible keymaps.

(Inspired by the Parsec library, written by Koen Claessen)

The processes are:

  • composable: in parallel using <|>, in sequence using monadic bind.
  • extensible: it is always possible to override a behaviour by combination of adjustPriority and <|>. (See also <|| for a convenient combination of the two.)
  • monadic: sequencing is done via monadic bind. (leveraging the whole battery of monadic tools that Haskell provides)

The processes can parse input, and write output that depends on it.

The semantics are quite obvious; only disjunction deserve a bit more explanation:

in p = (a <|> b), what happens if a and b recognize the same input (prefix), but produce conflicting output?

  • if the output is the same (as by the Eq class), then the processes (prefixes) are "merged"
  • if a Write is more prioritized than the other, the one with low priority will be discarded
  • otherwise, the output will be delayed until one of the branches can be discarded.
  • if there is no way to disambiguate, then no output will be generated anymore. This situation can be detected by using possibleActions however.

Synopsis

Documentation

data I ev w a Source #

Interactive process description

Instances

Monad (I event w) Source # 

Methods

(>>=) :: I event w a -> (a -> I event w b) -> I event w b #

(>>) :: I event w a -> I event w b -> I event w b #

return :: a -> I event w a #

fail :: String -> I event w a #

Functor (I event w) Source # 

Methods

fmap :: (a -> b) -> I event w a -> I event w b #

(<$) :: a -> I event w b -> I event w a #

Applicative (I ev w) Source # 

Methods

pure :: a -> I ev w a #

(<*>) :: I ev w (a -> b) -> I ev w a -> I ev w b #

(*>) :: I ev w a -> I ev w b -> I ev w b #

(<*) :: I ev w a -> I ev w b -> I ev w a #

Alternative (I ev w) Source # 

Methods

empty :: I ev w a #

(<|>) :: I ev w a -> I ev w a -> I ev w a #

some :: I ev w a -> I ev w [a] #

many :: I ev w a -> I ev w [a] #

Eq w => MonadPlus (I event w) Source # 

Methods

mzero :: I event w a #

mplus :: I event w a -> I event w a -> I event w a #

Eq w => MonadInteract (I event w) w event Source # 

Methods

write :: w -> I event w () Source #

eventBounds :: Maybe event -> Maybe event -> I event w event Source #

adjustPriority :: Int -> I event w () Source #

data P event w Source #

Operational representation of a process

Constructors

End 
(Show mid, Eq mid) => Chain (P event mid) (P mid w) 

Instances

(Show w, Show ev) => Show (P ev w) Source # 

Methods

showsPrec :: Int -> P ev w -> ShowS #

show :: P ev w -> String #

showList :: [P ev w] -> ShowS #

data InteractState event w Source #

Abstraction of the automaton state.

Constructors

Ambiguous [(Int, w, P event w)] 
Waiting 
Dead 
Running w (P event w) 

Instances

Monoid (InteractState event w) Source # 

Methods

mempty :: InteractState event w #

mappend :: InteractState event w -> InteractState event w -> InteractState event w #

mconcat :: [InteractState event w] -> InteractState event w #

class (Eq w, Monad m, Alternative m, Applicative m, MonadPlus m) => MonadInteract m w e | m -> w e where Source #

Abstraction of monadic interactive processes

Minimal complete definition

write, eventBounds, adjustPriority

Methods

write :: w -> m () Source #

Outputs a result.

eventBounds :: Ord e => Maybe e -> Maybe e -> m e Source #

Consumes and returns the next character. Fails if there is no input left, or outside the given bounds.

adjustPriority :: Int -> m () Source #

Instances

MonadInteract m w e => MonadInteract (StateT s m) w e Source # 

Methods

write :: w -> StateT s m () Source #

eventBounds :: Maybe e -> Maybe e -> StateT s m e Source #

adjustPriority :: Int -> StateT s m () Source #

Eq w => MonadInteract (I event w) w event Source # 

Methods

write :: w -> I event w () Source #

eventBounds :: Maybe event -> Maybe event -> I event w event Source #

adjustPriority :: Int -> I event w () Source #

important :: MonadInteract f w e => f a -> f a -> f a Source #

Just like '(<||)' but in prefix form. It deprioritizes the second argument.

(<||) :: MonadInteract f w e => f a -> f a -> f a infixl 3 Source #

(||>) :: MonadInteract f w e => f a -> f a -> f a Source #

option :: MonadInteract m w e => a -> m a -> m a Source #

option x p will either parse p or return x without consuming any input.

oneOf :: (Ord event, MonadInteract m w event) => [event] -> m event Source #

processOneEvent :: Eq w => P event w -> event -> ([w], P event w) Source #

computeState :: Eq w => P event w -> InteractState event w Source #

event :: (Ord event, MonadInteract m w event) => event -> m event Source #

Parses and returns the specified character.

events :: (Ord event, MonadInteract m w event) => [event] -> m [event] Source #

Parses and returns the specified list of events (lazily).

choice :: MonadInteract m w e => [m a] -> m a Source #

Combines all parsers in the specified list.

mkAutomaton :: Eq w => I ev w a -> P ev w Source #

idAutomaton :: (Ord a, Eq a) => P a a Source #

runWrite :: Eq w => P event w -> [event] -> [w] Source #

anyEvent :: (Ord event, MonadInteract m w event) => m event Source #

eventBetween :: (Ord e, MonadInteract m w e) => e -> e -> m e Source #

accepted :: Show ev => Int -> P ev w -> [[Text]] Source #