yi-0.6.2.3: The Haskell-Scriptable EditorSource codeContentsIndex
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 PEq 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
data I ev w a
data P event w
= End
| forall mid . (Show mid, PEq mid) => Chain (P event mid) (P mid w)
data InteractState event w
= Ambiguous [(Int, w, P event w)]
| Waiting
| Dead
| Running w (P event w)
class (PEq w, Monad m, Alternative m, Applicative m, MonadPlus m) => MonadInteract m w e | m -> w e where
write :: w -> m ()
eventBounds :: Ord e => Maybe e -> Maybe e -> m e
adjustPriority :: Int -> m ()
class PEq a where
equiv :: a -> a -> Bool
deprioritize :: MonadInteract f w e => f ()
(<||) :: MonadInteract f w e => f a -> f a -> f a
(||>) :: MonadInteract f w e => f a -> f a -> f a
option :: MonadInteract m w e => a -> m a -> m a
oneOf :: (Ord event, MonadInteract m w event) => [event] -> m event
processOneEvent :: PEq w => P event w -> event -> ([w], P event w)
computeState :: PEq w => P event w -> InteractState event w
event :: (Ord event, MonadInteract m w event) => event -> m event
events :: (Ord event, MonadInteract m w event) => [event] -> m [event]
choice :: MonadInteract m w e => [m a] -> m a
mkAutomaton :: PEq w => I ev w a -> P ev w
idAutomaton :: (Ord a, PEq a) => P a a
runWrite :: PEq w => P event w -> [event] -> [w]
anyEvent :: (Ord event, MonadInteract m w event) => m event
eventBetween :: (Ord e, MonadInteract m w e) => e -> e -> m e
accepted :: Show ev => Int -> P ev w -> [[String]]
Documentation
data I ev w a Source
Interactive process description
show/hide Instances
Monad (I event w)
Functor (I event w)
PEq w => MonadPlus (I event w)
Applicative (I ev w)
Alternative (I ev w)
PEq w => MonadInteract (I event w) w event
data P event w Source
Operational representation of a process
Constructors
End
forall mid . (Show mid, PEq mid) => Chain (P event mid) (P mid w)
show/hide Instances
(Show w, Show ev) => Show (P ev w)
data InteractState event w Source
Abstraction of the automaton state.
Constructors
Ambiguous [(Int, w, P event w)]
Waiting
Dead
Running w (P event w)
show/hide Instances
class (PEq w, Monad m, Alternative m, Applicative m, MonadPlus m) => MonadInteract m w e | m -> w e whereSource
Abstraction of monadic interactive processes
Methods
write :: w -> m ()Source
Outputs a result.
eventBounds :: Ord e => Maybe e -> Maybe e -> m eSource
Consumes and returns the next character. Fails if there is no input left, or outside the given bounds.
adjustPriority :: Int -> m ()Source
show/hide Instances
MonadInteract m w e => MonadInteract (StateT s m) w e
PEq w => MonadInteract (I event w) w event
class PEq a whereSource
Methods
equiv :: a -> a -> BoolSource
show/hide Instances
deprioritize :: MonadInteract f w e => f ()Source
(<||) :: MonadInteract f w e => f a -> f a -> f aSource
(||>) :: MonadInteract f w e => f a -> f a -> f aSource
option :: MonadInteract m w e => a -> m a -> m aSource
option x p will either parse p or return x without consuming any input.
oneOf :: (Ord event, MonadInteract m w event) => [event] -> m eventSource
processOneEvent :: PEq w => P event w -> event -> ([w], P event w)Source
computeState :: PEq w => P event w -> InteractState event wSource
event :: (Ord event, MonadInteract m w event) => event -> m eventSource
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 aSource
Combines all parsers in the specified list.
mkAutomaton :: PEq w => I ev w a -> P ev wSource
idAutomaton :: (Ord a, PEq a) => P a aSource
runWrite :: PEq w => P event w -> [event] -> [w]Source
anyEvent :: (Ord event, MonadInteract m w event) => m eventSource
eventBetween :: (Ord e, MonadInteract m w e) => e -> e -> m eSource
accepted :: Show ev => Int -> P ev w -> [[String]]Source
Produced by Haddock version 2.6.1