rasa-0.1.0.0: 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.

To react to events an extension defines a Scheduler which the user puts in their config file. The Scheduler defines listeners for events which the extension will react to. See Scheduler for more detailed information.

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 event to a file.

logger :: Scheduler ()
logger = do
  onInit $ liftIO $ writeFile "logs" "==Logs==\n"
  onEvent $ do
    evts <- use events
    mapM_ (liftIO . appendFile "logs" . (++ "\n") . show) evts
  onExit $ liftIO $ appendFile "logs" "==Done=="

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 eventListener

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 and focusDo
  • 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 Editor Action Source # 

Methods

get :: Action Editor #

put :: Editor -> Action () #

state :: (Editor -> (a, Editor)) -> Action a #

MonadReader Hooks Action Source # 

Methods

ask :: Action Hooks #

local :: (Hooks -> Hooks) -> Action a -> Action a #

reader :: (Hooks -> a) -> Action a #

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.

addBuffer :: Text -> Action () Source #

This adds a new buffer with the given text.

addBufferThen :: Text -> BufAction a -> Action a Source #

This adds a new buffer with the given text then performs the given BufAction agains that buffer.

nextBuf :: Action () Source #

Switches focus to the next buffer

prevBuf :: Action () Source #

Switches focus to the previous buffer

Buffer Actions

data BufAction a Source #

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

Within a BufAction you can:

  • Use liftIO for IO
  • Access/edit buffer extensions; see bufExt
  • Embed and sequence any BufActions from other extensions
  • Access/Edit the buffer's text

bufDo :: Monoid a => BufAction a -> Action a Source #

This lifts a BufAction to an Action which performs the BufAction on every buffer and collects the return values via mappend

focusDo :: BufAction a -> Action a Source #

This lifts a BufAction to an Action which performs the BufAction on the focused buffer.

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

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

replaceRange :: Range -> Text -> 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 -> Text -> 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

Persisting Extension State

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. (Show a, Typeable a, Default a) => Lens' Editor 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. (Show a, Typeable a, Default a) => Lens' Buffer 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. A buffer is the State of the BufAction monad transformer stack, so the type may be useful in defining lenses over your extension states.

text :: Lens' Buffer Text Source #

A lens into the text of the given buffer. Use within a BufAction.

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

txt <- use text

A lens over the current exit status of the editor, allows an extension to signal the editor to shutdown. If this is set the current events will finish processing, then the

Exit event will be dispatched, then the editor will exit. Use within an Action

exiting .= True

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.

Constructors

Keypress Char [Mod] 
Esc 
BS 
Enter 

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

data Scheduler a Source #

The Scheduler is how you can register your extension's actions to run at different points in the editor's event cycle.

The event cycle proceeds as follows:

    Init  (Runs ONCE)

    -- The following loops until an exit is triggered:
    BeforeEvent -> (any event) -> BeforeRender -> OnRender -> AfterRender

    Exit (Runs ONCE)

Each extension which wishes to perform actions exports a Scheduler () which the user inserts in their config file.

Instances

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.

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.

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

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

MyEventType -> Action () then it will be registered to listen for dispatched events of that type. Use within the Scheduler and add have the user add it to their config.

Built-in Event Hooks

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

Registers an action to be performed during the Initialization phase.

This phase occurs exactly ONCE when the editor starts up.

beforeEvent :: Action () -> Scheduler () Source #

Registers an action to be performed BEFORE each event phase.

beforeRender :: Action () -> Scheduler () 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.

onRender :: Action () -> Scheduler () Source #

Registers an action to be performed during each render phase.

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

afterRender :: Action () -> Scheduler () 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 () -> Scheduler () 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.

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 :: Range -> Lens' Buffer 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)