rasa-0.1.7: A modular text editor

Copyright(C) 2016 Chris Penner
LicenseMIT
MaintainerChris Penner <christopher.penner@gmail.com>
Safe HaskellNone
LanguageHaskell2010

Rasa.Ext

Contents

Description

This module contains the public API for building an extension for Rasa. It re-exports the parts of rasa that are public API for creating extensions.

There are two main things that an extension can do, either react to editor events, or expose useful actions and/or state for other extensions to use.

Whether performing its own actions or being used by a different extension an extension will want to define some Actions to perform. Actions can operate over buffers or even perform IO and comprise the main way in which extensons do what they need to do. Read more here: Action, BufAction.

To sum it all up, Here's an example of a simple logging extension that simply writes each keypress to a file.

logKeypress :: Keypress -> Action ()
logKeypress (Keypress char _) = liftIO $ appendFile "logs" ("You pressed " ++ [char] ++ "\n")

logger :: Action HookId
logger = do
  onInit $ liftIO $ writeFile "logs" "==Logs==\n"
  onEveryTrigger_ logKeypress
  onExit $ liftIO $ appendFile "logs" "==Done=="

Check out this tutorial on building extensions, it's also just a great way to learn how the editor works: <https://github.com/ChrisPenner/rasa/blob/master/docs/Building-An-Extension.md Building an Extension>.

Synopsis

Editor Actions

data Action a Source #

This is a monad-transformer stack for performing actions against the editor. You register Actions to be run in response to events using onEveryTrigger

Within an Action you can:

  • Use liftIO for IO
  • Access/edit extensions that are stored globally, see ext
  • Embed any Actions exported other extensions
  • Embed buffer actions using bufDo or buffersDo
  • Add/Edit/Focus buffers and a few other Editor-level things, see the Directive module.

Instances

Monad Action Source # 

Methods

(>>=) :: Action a -> (a -> Action b) -> Action b #

(>>) :: Action a -> Action b -> Action b #

return :: a -> Action a #

fail :: String -> Action a #

Functor Action Source # 

Methods

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

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

Applicative Action Source # 

Methods

pure :: a -> Action a #

(<*>) :: Action (a -> b) -> Action a -> Action b #

(*>) :: Action a -> Action b -> Action b #

(<*) :: Action a -> Action b -> Action a #

MonadIO Action Source # 

Methods

liftIO :: IO a -> Action a #

MonadState ActionState Action Source # 

doAsync :: IO (Action ()) -> Action () Source #

doAsync allows you to perform a task asynchronously and then apply the result. In doAsync asyncAction, asyncAction is an IO which resolves to an Action, note that the context in which the second action is executed is NOT the same context in which doAsync is called; it is likely that text and other state have changed while the IO executed, so it's a good idea to check (inside the applying Action) that things are in a good state before making changes. Here's an example:

asyncCapitalize :: Action ()
asyncCapitalize = do
  txt <- focusDo $ use text
  -- We give doAsync an IO which resolves in an action
  doAsync $ ioPart txt

ioPart :: Text -> IO (Action ())
ioPart txt = do
  result <- longAsyncronousCapitalizationProgram txt
  -- Note that this returns an Action, but it's still wrapped in IO
  return $ maybeApplyResult txt result

maybeApplyResult :: Text -> Text -> Action ()
maybeApplyResult oldTxt capitalized = do
  -- We get the current buffer's text, which may have changed since we started
  newTxt <- focusDo (use text)
  if newTxt == oldTxt
    -- If the text is the same as it was, we can apply the transformation
    then focusDo (text .= capitalized)
    -- Otherwise we can choose to re-queue the whole action and try again
    -- Or we could just give up.
    else asyncCapitalize

exit :: Action () Source #

This signals to the editor that you'd like to shutdown. The current events will finish processing, then the onExit hook will run, then the editor will exit.

Managing Buffers

newBuffer :: YiString -> Action BufRef Source #

This adds a new buffer with the given text.

nextBufRef :: BufRef -> Action BufRef Source #

Gets BufRef that comes after the one provided

prevBufRef :: BufRef -> Action BufRef Source #

Gets BufRef that comes before the one provided

getBufRefs :: Action [BufRef] Source #

Returns an up-to-date list of all BufRefs

getBuffers :: Action [(BufRef, Buffer)] Source #

Returns an up-to-date list of all Buffers, returned values are read-only; altering them has no effect on the actual stored buffers. This function is useful for renderers.

getBuffer :: BufRef -> Action (Maybe Buffer) Source #

Returns the Buffer for a BufRef if it still exists. This is read-only; altering the buffer has no effect on the stored buffer. This function is useful for renderers.

Working with Buffers

data BufAction a Source #

This is a monad-transformer stack for performing actions on a specific buffer. You run BufActions by embedding them in a Action via bufferDo or buffersDo

Within a BufAction you can:

  • Use liftAction to run an Action; It is your responsibility to ensure that any nested Actions don't edit the Buffer which the current BufAction is editing; behaviour is undefined if this occurs.
  • Use liftIO for IO
  • Access/Edit the buffer's text
  • Access/edit buffer extensions; see bufExt
  • Embed and sequence BufActions from other extensions

liftAction :: Action a -> BufAction a Source #

This lifts up an Action to be run inside a BufAction

it is your responsibility to ensure that any nested Actions don't edit the Buffer which the current BufAction is editing; behaviour is undefined if this occurs.

bufDo :: BufRef -> BufAction a -> Action (Maybe a) Source #

This lifts a BufAction to an Action which performs the BufAction on the buffer referred to by the BufRef If the buffer referred to no longer exists this returns Action Nothing.

buffersDo :: BufAction a -> Action [a] Source #

This lifts a BufAction to an Action which performs the BufAction on every buffer and collects the return values as a list.

Working with Text

overRange :: Range -> (YiString -> YiString) -> BufAction () Source #

Runs the given function over the text in the range, replacing it with the results.

replaceRange :: Range -> YiString -> BufAction () Source #

Replaces the text in the given range from the buffer.

deleteRange :: Range -> BufAction () Source #

Deletes the text in the given range from the buffer.

insertAt :: Coord -> YiString -> BufAction () Source #

Inserts text into the buffer at the given Coord.

sizeOf :: YiString -> Coord Source #

Returns the number of rows and columns that a chunk of text spans as a Coord

Working with Extensions

Extension states for ALL the extensions installed are stored in the same map keyed by their TypeRep so if more than one extension uses the same type then they'll conflict. This is easily solved by simply using a newtype around any types which other extensions may use (your own custom types don't need to be wrapped). For example if your extension stores a counter as an Int, wrap it in your own custom Counter newtype when storing it.

Because Extension states are stored by their TypeRep, they must define an instance of Typeable, luckily GHC can derive this for you.

It is also required for all extension states to define an instance of Default, this is because accessing an extension which has not yet been stored will result in the default value.

If there's no default value that makes sense for your type, you can define a default of Nothing and pattern match on its value when you access it.

Extensions may store state persistently for later access or for other extensions to access. Because Rasa can't possibly know the types of the state that extensions will store it uses a clever workaround wherein extension states are stored in a map of TypeRep -> Ext which is coerced into the proper type when it's extracted. The interface to extract or alter a given extension is to use the ext and bufExt lenses. Simply use them as though they were lenses to an object of your type and it'll all work out.

Since it's polymorphic, if ghc can't figure out the type the result is supposed to be then you'll need to help it out. In practice you won't typically need to do this unless you're doing something complicated.

ext :: forall a e. (Show a, Typeable a, Default a, HasEditor e) => Lens' e a Source #

ext is a lens which will focus the extension state that matches the type inferred as the focal point. It's a little bit of magic, if you treat the focus as a member of your extension state it should just work out.

This lens falls back on the extension's Default instance (when getting) if nothing has yet been stored.

bufExt :: forall a s. (Show a, Typeable a, Default a, HasBuffer s) => Lens' s a Source #

bufExt is a lens which will focus a given extension's state within a buffer (within a BufAction). The lens will automagically focus the required extension by using type inference. It's a little bit of magic, if you treat the focus as a member of your extension state it should just work out.

This lens falls back on the extension's Default instance (when getting) if nothing has yet been stored.

Accessing/Editing Context

data Buffer Source #

A buffer, holds the text in the buffer and any extension states that are set on the buffer.

class HasBuffer a Source #

This allows creation of polymorphic lenses over any type which has access to a Buffer

Minimal complete definition

buffer

data BufRef Source #

An opaque reference to a buffer (The contained Int is not meant to be altered). It is possible for references to become stale if buffers are deleted. Operations over invalid BufRef's are simply ignored and return Nothing if a value was expected.

class HasEditor a Source #

This allows polymorphic lenses over anything that has access to an Editor context

Minimal complete definition

editor

text :: HasBuffer b => Lens' b YiString Source #

This lens focuses the text of the in-scope buffer.

A lens over the buffer's Text as a YiString. Use within a BufAction:

txt <- use text

Events

data Keypress Source #

This event is dispatched in response to keyboard key presses. It contains both the char that was pressed and any modifiers (Mod) that where held when the key was pressed.

data Mod Source #

This represents each modifier key that could be pressed along with a key.

Constructors

Ctrl 
Alt 
Shift 

Instances

Eq Mod Source # 

Methods

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

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

Show Mod Source # 

Methods

showsPrec :: Int -> Mod -> ShowS #

show :: Mod -> String #

showList :: [Mod] -> ShowS #

Dealing with events

type Hooks = Map TypeRep [Hook] Source #

A map of Event types to a list of listeners for that event

data Hook Source #

A wrapper around event listeners so they can be stored in Hooks.

data HookId Source #

Instances

Eq HookId Source # 

Methods

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

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

dispatchEvent :: Typeable a => a -> Action () Source #

Use this to dispatch an event of any type, any hooks which are listening for this event will be triggered with the provided event. Use this within an Action.

onEveryTrigger :: forall a. Typeable a => (a -> Action ()) -> Action HookId Source #

This registers an event listener hook, as long as the listener is well-typed similar to this:

MyEventType -> Action () then it will be triggered on all dispatched events of that type. It returns an ID which may be used with removeListener to cancel the listener

onEveryTrigger_ :: forall a. Typeable a => (a -> Action ()) -> Action () Source #

onNextEvent :: forall a. Typeable a => (a -> Action ()) -> Action () Source #

This acts as onEveryTrigger but listens only for the first event of a given type.

removeListener :: HookId -> Action () Source #

This removes a listener and prevents it from responding to any more events.

eventProvider :: Typeable a => IO a -> Action () Source #

This function takes an IO which results in some Event, it runs the IO asynchronously and dispatches the event, then repeats the process all over again. Use this inside the onInit scheduler to register an event listener for some event (e.g. keypresses or network activity)

Built-in Event Hooks

onInit :: Action () -> Action () Source #

Registers an action to be performed during the Initialization phase.

This phase occurs exactly ONCE when the editor starts up. Though arbitrary actions may be performed in the configuration block; it's recommended to embed such actions in the onInit event listener so that all event listeners are registered before anything Actions occur.

beforeEveryEvent :: Action () -> Action HookId Source #

Registers an action to be performed BEFORE each event phase.

beforeEveryRender :: Action () -> Action HookId Source #

Registers an action to be performed BEFORE each render phase.

This is a good spot to add information useful to the renderer since all actions have been performed. Only cosmetic changes should occur during this phase.

onEveryRender :: Action () -> Action HookId Source #

Registers an action to be performed during each render phase.

This phase should only be used by extensions which actually render something.

afterEveryRender :: Action () -> Action HookId Source #

Registers an action to be performed AFTER each render phase.

This is useful for cleaning up extension state that was registered for the renderer, but needs to be cleared before the next iteration.

onExit :: Action () -> Action () Source #

Registers an action to be performed during the exit phase.

This is only triggered exactly once when the editor is shutting down. It allows an opportunity to do clean-up, kill any processes you've started, or save any data before the editor terminates.

onBufAdded :: (BufRef -> Action ()) -> Action HookId Source #

Registers an action to be performed after a new buffer is added.

The supplied function will be called with a BufRef to the new buffer, and the resulting Action will be run.

Ranges

data Range Source #

This represents a range between two coordinates (Coord)

Constructors

Range Coord Coord 

Instances

Eq Range Source # 

Methods

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

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

Ord Range Source # 

Methods

compare :: Range -> Range -> Ordering #

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

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

(>) :: Range -> Range -> Bool #

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

max :: Range -> Range -> Range #

min :: Range -> Range -> Range #

Show Range Source # 

Methods

showsPrec :: Int -> Range -> ShowS #

show :: Range -> String #

showList :: [Range] -> ShowS #

data Coord Source #

(Coord Row Column) represents a char in a block of text. (zero indexed) e.g. Coord 0 0 is the first character in the text, Coord 2 1 is the second character of the third row

Constructors

Coord Int Int 

Instances

newtype Offset Source #

An Offset represents an exact position in a file as a number of characters from the start.

Constructors

Offset Int 

Instances

data Span a Source #

A span which maps a piece of Monoidal data over a range.

Constructors

Span 

Fields

Instances

Functor Span Source # 

Methods

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

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

Eq a => Eq (Span a) Source # 

Methods

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

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

Show a => Show (Span a) Source # 

Methods

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

show :: Span a -> String #

showList :: [Span a] -> ShowS #

combineSpans :: forall a. Monoid a => [Span a] -> [(Coord, a)] Source #

Combines a list of spans containing some monoidal data into a list of offsets with with the data that applies from each Offset forwards.

asCoord :: YiString -> Iso' Offset Coord Source #

Given the text you're operating over, creates an iso from an Offset to a Coord.

clampCoord :: YiString -> Coord -> Coord Source #

This will restrict a given Coord to a valid one which lies within the given text.

clampRange :: YiString -> Range -> Range Source #

This will restrict a given Range to a valid one which lies within the given text.

range :: HasBuffer s => Range -> Lens' s YiString Source #

A lens over text which is encompassed by a Range

sizeOfR :: Range -> Coord Source #

Returns the number of rows and columns that a Range spans as a Coord

afterC :: Coord -> Lens' YiString YiString Source #

A lens over text after a given Coord

beforeC :: Coord -> Lens' YiString YiString Source #

A lens over text before a given Coord

moveRange :: Coord -> Range -> Range Source #

Moves a Range by a given Coord It may be unintuitive, but for (Coord row col) a given range will be moved down by row and to the right by col.

moveRangeByN :: Int -> Range -> Range Source #

Moves a range forward by the given amount

moveCursorByN :: Int -> Coord -> Coord Source #

Moves a Coord forward by the given amount of columns

Useful Utilities

asText :: Iso' YiString Text Source #

An iso which converts to/from YiString -> Text

asString :: Iso' YiString String Source #

An iso which converts to/from YiString -> String

asLines :: Iso' YiString [YiString] Source #

An iso which converts to/from YiString -> [YiString]

clamp :: Int -> Int -> Int -> Int Source #

clamp min max val restricts val to be within min and max (inclusive)