yi-0.12.1: The Haskell-Scriptable Editor

LicenseGPL-2
Maintaineryi-devel@googlegroups.com
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell2010
Extensions
  • ScopedTypeVariables
  • OverloadedStrings
  • RecursiveDo
  • RankNTypes
  • ExplicitForAll
  • NondecreasingIndentation
  • LambdaCase

Yi.Core

Contents

Description

The core actions of Yi. This module is the link between the editor and the UI. Key bindings, and libraries should manipulate Yi through the interface defined here.

Synopsis

Construction and destruction

startEditor :: Config -> Maybe Editor -> IO () Source

Start up the editor, setting any state with the user preferences and file names passed in, and turning on the UI

quitEditor :: YiM () Source

Quit.

User interaction

suspendEditor :: YiM () Source

Suspend the program

Global editor actions

errorEditor :: Text -> YiM () Source

Show an error on the status line and log it.

closeWindow :: YiM () Source

Close the current window. If this is the last window open, quit the program.

CONSIDER: call quitEditor when there are no other window in the interactive function. (Not possible since the windowset type disallows it -- should it be relaxed?)

closeWindowEmacs :: YiM () Source

This is a like closeWindow but with emacs behaviour of C-x 0: if we're trying to close the minibuffer or last buffer in the editor, then just print a message warning the user about it rather closing mini or quitting editor.

Interacting with external commands

runProcessWithInput :: String -> String -> YiM String Source

Pipe a string through an external command, returning the stdout chomp any trailing newline (is this desirable?)

Todo: varients with marks?

startSubprocess :: FilePath -> [String] -> (Either SomeException ExitCode -> YiM x) -> YiM BufferRef Source

Start a subprocess with the given command and arguments.

Misc

withSyntax :: (Show x, YiAction a x) => (forall syntax. Mode syntax -> syntax -> a) -> YiM () Source

forkAction Source

Arguments

:: (YiAction a x, Show x) 
=> IO Bool

runs after we insert the action: this may be a thread delay or a thread suicide or whatever else; when delay returns False, that's our signal to terminate the thread.

-> IsRefreshNeeded

should we refresh after each action

-> a

The action to actually run

-> YiM ThreadId 

Runs a YiM action in a separate thread.

Notes:

  • It seems to work but I don't know why
  • Maybe deadlocks?
  • If you're outputting into the Yi window, you should really limit the rate at which you do so: for example, the Pango front-end will quite happily segfault/double-free if you output too fast.

I am exporting this for those adventurous to play with but I have only discovered how to do this a night before the release so it's rather experimental. A simple function that prints a message once a second, 5 times, could be written like this:

printer :: YiM ThreadId
printer = do
  mv <- io $ newMVar (0 :: Int)
  forkAction (suicide mv) MustRefresh $ do
    c <- io $ do
      modifyMVar_ mv (return . succ)
      tryReadMVar mv
    case c of
      Nothing -> printMsg "messaging unknown time"
      Just x -> printMsg $ "message #" <> showT x
  where
    suicide mv = tryReadMVar mv >>= case
      Just i | i >= 5 -> return True
      _ -> threadDelay 1000000 >> return False