rasa-0.1.8: 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 ()
logger = do
  onInit $ liftIO $ writeFile "logs" "==Logs==\n"
  -- Listeners should also be registered using 'onInit'.
  -- It ensures all listeners are ready before any actions occur.
  onInit $ 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: Extension-Guide.

Synopsis

Editor Actions

data Action a Source #

This is a monad for performing actions against the editor. You can 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 Rasa.Internal.Actions 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 # 

exit :: Action () Source #

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

Managing Buffers

newBuffer :: YiString -> Action BufRef Source #

This adds a new buffer with the given text, returning a reference to that buffer.

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 Buffer Source #

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

class HasBuffer a where Source #

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

Minimal complete definition

buffer

Methods

buffer :: Lens' a Buffer Source #

data BufRef Source #

An opaque reference to a buffer. When operating over a BufRef Rasa checks if the Buffer still exists and simply ignores any operations over non-existent buffers; typically returning Nothing

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

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

class HasEditor a Source #

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

Minimal complete definition

editor

getText :: BufAction YiString Source #

Returns the text of the current buffer

getRange :: CrdRange -> BufAction YiString Source #

Gets the range of text from the buffer

Actions over Buffers

data BufAction a Source #

This is a monad 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:

Instances

Monad BufAction Source # 

Methods

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

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

return :: a -> BufAction a #

fail :: String -> BufAction a #

Functor BufAction Source # 

Methods

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

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

Applicative BufAction Source # 

Methods

pure :: a -> BufAction a #

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

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

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

MonadIO BufAction Source # 

Methods

liftIO :: IO a -> BufAction a #

liftAction :: Action r -> BufAction r Source #

This lifts up an Action to be run inside a BufAction

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: 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 :: CrdRange -> (YiString -> YiString) -> BufAction () Source #

Runs function over given range of text

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

Replaces the text in the given range with the given text.

deleteRange :: CrdRange -> 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.

class HasExts s where Source #

Members of this class have access to editor extensions.

Minimal complete definition

exts

Methods

exts :: Lens' s (Map TypeRep Ext) Source #

This lens focuses the Extensions States

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

This 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.

class HasBufExts s where Source #

Members of this class have access to buffer extensions. (Each Buffer is a member of this class)

Minimal complete definition

bufExts

Methods

bufExts :: Lens' s (Map TypeRep Ext) Source #

This lens focuses the Extensions States map of the in-scope buffer.

bufExt :: forall a s. (Show a, Typeable a, Default a, HasBufExts 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.

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

data ListenerId Source #

An opaque reverence to a specific registered event-listener. A ListenerId is used only to remove listeners later with removeListener.

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

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

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

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

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

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

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

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

removeListener :: ListenerId -> Action () Source #

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

Built-in Event Listeners

onInit :: forall a. Action a -> 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 :: forall a. Action a -> Action ListenerId Source #

Registers an action to be performed BEFORE each event phase.

beforeEveryEvent_ :: forall a. Action a -> Action () Source #

beforeNextEvent :: forall a. Action a -> Action () Source #

Registers an action to be performed ONCE before only the NEXT event phase.

beforeEveryRender :: forall a. Action a -> Action ListenerId 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.

beforeEveryRender_ :: forall a. Action a -> Action () Source #

beforeNextRender :: forall a. Action a -> Action () Source #

Registers an action to be performed ONCE before only the NEXT render phase.

onEveryRender :: forall a. Action a -> Action ListenerId Source #

Registers an action to be performed during each render phase.

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

onEveryRender_ :: forall a. Action a -> Action () Source #

onNextRender :: forall a. Action a -> Action () Source #

Registers an action to be performed ONCE before only the NEXT render phase.

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

afterEveryRender :: forall a. Action a -> Action ListenerId 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.

afterEveryRender_ :: forall a. Action a -> Action () Source #

afterNextRender :: forall a. Action a -> Action () Source #

Registers an action to be performed after the NEXT render phase.

onExit :: forall a. Action a -> 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 :: forall a. (BufRef -> Action a) -> Action ListenerId 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.

onBufTextChanged :: forall a. (CrdRange -> YiString -> Action a) -> Action ListenerId Source #

This is fired every time text in a buffer changes.

The range of text which was altered and the new value of that text are provided inside a BufTextChanged event.

Working with Async Events/Actions

type Dispatcher = forall a. Typeable a => a -> IO () Source #

This is a type alias to make defining your event provider functions easier; It represents the function your event provider function will be passed to allow dispatching events. Using this type requires the Rank2Types language pragma.

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

dispatchActionAsync allows you to perform a task asynchronously and then apply the result. In dispatchActionAsync 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 dispatchActionAsync 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 dispatchActionAsync an IO which resolves in an action
  dispatchActionAsync $ 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

dispatchEventAsync :: 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

asyncEventProvider :: (Dispatcher -> IO ()) -> Action () Source #

This allows long-running IO processes to provide Events to Rasa asyncronously.

Don't let the type signature confuse you; it's much simpler than it seems.

Let's break it down:

(Dispatcher -> IO ()): Dispatcher is a type alias just to make defining your own functions easier; Using Dispatcher with asyncEventProvider requires the Rank2Types language pragma.

This type as a whole represents a function which accepts a Dispatcher and returns an IO; the dispatcher itself accepts data of ANY Typeable type and emits it as an event (see the Rasa.Internal.Events).

When you call asyncEventProvider you pass it a function which accepts a dispatch function as an argument and then calls it with various events within the resulting IO.

Note that asyncEventProvider calls forkIO internally, so there's no need to do that yourself.

Here's a simple example which fires a Timer event every second.

{-# language Rank2Types #-}
data Timer = Timer
myTimer :: Dispatcher -> IO ()
myTimer dispatch = forever $ dispatch Timer >> threadDelay 1000000

myAction :: Action ()
myAction = onInit $ asyncEventProvider myTimer

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

Don't let the type signature confuse you; it's much simpler than it seems. The first argument is a function which takes an action provider; the action provider will be passed a dispatch function which can be called as often as you like with Action ()s. When it is passed an Action it forks off an IO to dispatch that Action to the main event loop. Note that the dispatch function calls forkIO on its own; so there's no need for you to do so.

Use this function when you have some long-running process which dispatches multiple Actions.

Ranges

data Range a b Source #

This represents a range between two coordinates (Coord)

Constructors

Range 

Fields

Instances

Bifunctor Range Source # 

Methods

bimap :: (a -> b) -> (c -> d) -> Range a c -> Range b d #

first :: (a -> b) -> Range a c -> Range b c #

second :: (b -> c) -> Range a b -> Range a c #

Bitraversable Range Source # 

Methods

bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> Range a b -> f (Range c d) #

Bifoldable Range Source # 

Methods

bifold :: Monoid m => Range m m -> m #

bifoldMap :: Monoid m => (a -> m) -> (b -> m) -> Range a b -> m #

bifoldr :: (a -> c -> c) -> (b -> c -> c) -> c -> Range a b -> c #

bifoldl :: (c -> a -> c) -> (c -> b -> c) -> c -> Range a b -> c #

(Eq b, Eq a) => Eq (Range a b) Source # 

Methods

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

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

(Ord a, Ord b) => Ord (Range a b) Source # 

Methods

compare :: Range a b -> Range a b -> Ordering #

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

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

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

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

max :: Range a b -> Range a b -> Range a b #

min :: Range a b -> Range a b -> Range a b #

(Show b, Show a) => Show (Range a b) Source # 

Methods

showsPrec :: Int -> Range a b -> ShowS #

show :: Range a b -> String #

showList :: [Range a b] -> ShowS #

type CrdRange = Range Coord Coord Source #

A type alias to Range' which specializes the types to Coords.

type Coord = Coord' Int Int Source #

A type alias to Coord' which specializes the types to integers.

data Coord' a b 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 

Fields

Instances

Bifunctor Coord' Source # 

Methods

bimap :: (a -> b) -> (c -> d) -> Coord' a c -> Coord' b d #

first :: (a -> b) -> Coord' a c -> Coord' b c #

second :: (b -> c) -> Coord' a b -> Coord' a c #

Biapplicative Coord' Source # 

Methods

bipure :: a -> b -> Coord' a b #

(<<*>>) :: Coord' (a -> b) (c -> d) -> Coord' a c -> Coord' b d #

(*>>) :: Coord' a b -> Coord' c d -> Coord' c d #

(<<*) :: Coord' a b -> Coord' c d -> Coord' a b #

(Eq b, Eq a) => Eq (Coord' a b) Source # 

Methods

(==) :: Coord' a b -> Coord' a b -> Bool #

(/=) :: Coord' a b -> Coord' a b -> Bool #

(Num a, Num b) => Num (Coord' a b) Source # 

Methods

(+) :: Coord' a b -> Coord' a b -> Coord' a b #

(-) :: Coord' a b -> Coord' a b -> Coord' a b #

(*) :: Coord' a b -> Coord' a b -> Coord' a b #

negate :: Coord' a b -> Coord' a b #

abs :: Coord' a b -> Coord' a b #

signum :: Coord' a b -> Coord' a b #

fromInteger :: Integer -> Coord' a b #

(Ord a, Ord b) => Ord (Coord' a b) Source # 

Methods

compare :: Coord' a b -> Coord' a b -> Ordering #

(<) :: Coord' a b -> Coord' a b -> Bool #

(<=) :: Coord' a b -> Coord' a b -> Bool #

(>) :: Coord' a b -> Coord' a b -> Bool #

(>=) :: Coord' a b -> Coord' a b -> Bool #

max :: Coord' a b -> Coord' a b -> Coord' a b #

min :: Coord' a b -> Coord' a b -> Coord' a b #

(Show b, Show a) => Show (Coord' a b) Source # 

Methods

showsPrec :: Int -> Coord' a b -> ShowS #

show :: Coord' a b -> String #

showList :: [Coord' a b] -> ShowS #

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 b Source #

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

Constructors

Span a b 

Instances

Bifunctor Span Source # 

Methods

bimap :: (a -> b) -> (c -> d) -> Span a c -> Span b d #

first :: (a -> b) -> Span a c -> Span b c #

second :: (b -> c) -> Span a b -> Span a c #

Functor (Span a) Source # 

Methods

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

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

(Eq b, Eq a) => Eq (Span a b) Source # 

Methods

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

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

(Show b, Show a) => Show (Span a b) Source # 

Methods

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

show :: Span a b -> String #

showList :: [Span a b] -> ShowS #

overRow :: (Int -> Int) -> Coord -> Coord Source #

Applies a function over the row of a Coord

overCol :: (Int -> Int) -> Coord -> Coord Source #

Applies a function over the column of a Coord

coordRow :: forall a b a. Lens (Coord' a b) (Coord' a b) a a Source #

coordCol :: forall a b b. Lens (Coord' a b) (Coord' a b) b b Source #

overBoth :: Bifunctor f => (a -> b) -> f a a -> f b b Source #

Applies a function over both functors in any Bifunctor.

combineSpans :: forall a. Monoid a => [Span CrdRange 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 -> CrdRange -> CrdRange Source #

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

rStart :: forall a b a. Lens (Range a b) (Range a b) a a Source #

rEnd :: forall a b b. Lens (Range a b) (Range a b) b b Source #

sizeOfR :: CrdRange -> 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 -> CrdRange -> CrdRange 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 -> CrdRange -> CrdRange 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)