rasa-0.1.12: 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")
logKeypress _ = return ()

logger :: Action ()
logger = do
  liftIO $ writeFile "logs" "==Logs==\n"
  onKeypress 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

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

Retrieve a buffer. This is read-only for loggingrenderingdebugging purposes only.

Managing Buffers

addBuffer :: YiString -> App BufRef Source #

Adds a new buffer and returns the BufRef

nextBufRef :: BufRef -> App BufRef Source #

Gets BufRef that comes after the one provided

prevBufRef :: BufRef -> App BufRef Source #

Gets BufRef that comes before the one provided

getBufRefs :: App [BufRef] Source #

Returns an up-to-date list of all BufRefs

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.

getText :: BufAction YiString Source #

Returns the text of the current buffer

getRange :: CrdRange -> BufAction YiString Source #

Gets the range of text from the buffer

getBufRef :: BufAction BufRef Source #

Gets the current buffer's BufRef

Actions over Buffers

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

This lifts a BufAction to an App 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 -> App [a] Source #

This lifts a BufAction to an App 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

getLineRange :: Row -> BufAction (Maybe CrdRange) Source #

Gets the range representing a given row (if that row exists)

getBufExt :: (Typeable s, Show s, Default s) => BufAction s Source #

Retrieve some buffer extension state

setBufExt :: (Typeable s, Show s, Default s) => s -> BufAction () Source #

Set some buffer extension state

overBufExt :: (Typeable s, Show s, Default s) => (s -> s) -> BufAction () Source #

Set some buffer extension state

Events

dispatchBufEvent :: (Monoid result, Typeable eventType, Typeable result) => eventType -> BufAction result Source #

Dispatches an event of any type to the BufAction's buffer. See dispatchEvent

addBufListener :: (Typeable eventType, Typeable result, Monoid result) => (eventType -> BufAction result) -> BufAction ListenerId Source #

Adds a listener to the BufAction's buffer. See addListener

addBufListener_ :: (Typeable eventType, Typeable result, Monoid result) => (eventType -> BufAction result) -> BufAction () Source #

removeBufListener :: ListenerId -> BufAction () Source #

Removes a listener from the BufAction's buffer. See removeListener

Built-in 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 
Meta 

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 #

dispatchKeypress :: Keypress -> App () Source #

Dispatch a Keypress event.

data BufAdded Source #

This event is dispatched after adding a new buffer. The contained BufRef refers to the new buffer.

Constructors

BufAdded BufRef 

data BufTextChanged Source #

This is triggered when text in a buffer is changed. The Event data includes the CrdRange that changed and the new text which is now contined in that range.

Built-in Event Listeners

beforeEveryRender :: App a -> App 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.

onEveryRender :: App a -> App ListenerId Source #

Registers an action to be performed during each render phase.

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

afterEveryRender :: App a -> App 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.

onBufAdded :: (BufAdded -> App result) -> App 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 App will be run.

onBufAdded_ :: (BufAdded -> App result) -> App () Source #

onEveryNewBuffer :: BufAction a -> App ListenerId Source #

Run the given BufAction over all new buffers

onBufTextChanged :: (BufTextChanged -> BufAction result) -> BufAction 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.

onKeypress :: (Keypress -> App result) -> App ListenerId Source #

Trigger an App on a Keypress

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 a, Show b) => 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 a, Show b) => 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

Styles

A common representation for text styling

fg :: Color -> Style Source #

Create a new Style with the given Color as the foreground.

bg :: Color -> Style Source #

Create a new Style with the given Color as the background.

flair :: Flair -> Style Source #

Create a new Style with the given Flair as its flair.

data Color Source #

These represent the possible colors for fg or bg. DefColor represents the renderer's default color.

Instances

Eq Color Source # 

Methods

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

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

Show Color Source # 

Methods

showsPrec :: Int -> Color -> ShowS #

show :: Color -> String #

showList :: [Color] -> ShowS #

data Flair Source #

These represent the possible extra attributes which may be applied. DefFlair represents the renderer's default text attributes.

Instances

Eq Flair Source # 

Methods

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

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

Show Flair Source # 

Methods

showsPrec :: Int -> Flair -> ShowS #

show :: Flair -> String #

showList :: [Flair] -> ShowS #

newtype Style Source #

A container which holds a foreground color, background color, and a flair. a Nothing represents that we should not change that attribute.

Constructors

Style (Maybe Color, Maybe Color, Maybe Flair) 

Instances

Eq Style Source # 

Methods

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

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

Show Style Source # 

Methods

showsPrec :: Int -> Style -> ShowS #

show :: Style -> String #

showList :: [Style] -> ShowS #

Monoid Style Source #

The monoid instance replaces any attributes which have a Just in the new Style and persists any that are Nothing in the new style (using Alternative for Maybe)

Methods

mempty :: Style #

mappend :: Style -> Style -> Style #

mconcat :: [Style] -> Style #

Default Style Source # 

Methods

def :: Style #

addStyleProvider :: BufAction Styles -> BufAction ListenerId Source #

Pass this a BufAction which computes styles based on the current buffer and they'll be collected for the renderer.

getStyles :: BufAction Styles Source #

Collect all provided styles, this is useful for renderers.

styleText :: YiString -> Style -> RenderInfo Source #

Add a style to some text resulting in a RenderInfo

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)

cropToViewport :: Height -> ScrollPos -> RenderInfo -> RenderInfo Source #

Crop text verticaly to only the visible portion according to viewport height and scroll position.

Common Types/Interfaces

These exist to help unify the interfaces of many different extensions without requiring them to depend upon each other. Use them liberally in your own extensions.

type Width = Int Source #

data RenderInfo Source #

RenderInfo is the data necessary to render something; it consists of a block of text with its associated styles. It is a Monoid and can be appended with other RenderInfos.

Constructors

RenderInfo YiString Styles 

Instances

Monoid RenderInfo Source #

Appends to RenderInfo by appending the text and styles while preserving proper text/style alignment

Renderable RenderInfo Source # 

class Renderable r where Source #

Represents how to render an entity

Minimal complete definition

render

Methods

render :: Width -> Height -> ScrollPos -> r -> App (Maybe RenderInfo) Source #

module Eve