rasa-ext-views-0.1.1: Rasa Ext managing rendering views

Safe HaskellNone
LanguageHaskell2010

Rasa.Ext.Views

Synopsis

Documentation

views :: Scheduler () Source #

Main export from the views extension, add this to your rasa config.

getViews :: Action Views Source #

Retrieve Views.

getBufferViews :: Action (Maybe (BiTree Split (View, Buffer))) Source #

Retrieve a tree populated with views and their associated buffer

rotate :: Action () Source #

Flip all Horizontal splits to Vertical ones and vice versa.

closeInactive :: Action () Source #

Close all inactive viewports

focusViewLeft :: Action () Source #

Move focus from any viewports one viewport to the left

focusViewRight :: Action () Source #

Move focus from any viewports one viewport to the right

focusViewAbove :: Action () Source #

Move focus from any viewports one viewport above

focusViewBelow :: Action () Source #

Move focus from any viewports one viewport below

hSplit :: Action () Source #

Split active views horizontally

vSplit :: Action () Source #

Split active views vertically

addSplit :: BufRef -> Action () Source #

Add a new split at the top level in the given direction containing the given buffer.

nextBuf :: Action () Source #

Select the next buffer in any active viewports

prevBuf :: Action () Source #

Select the previous buffer in any active viewports

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

Run a bufAction over all focused buffers and return any results.

focusedBufs :: Action [BufRef] Source #

Get bufRefs for all buffers that are selected in at least one viewport

data Dir Source #

  • Hor denotes a horizontal split.
  • Vert denotes a vertical split.

Constructors

Hor 
Vert 

Instances

Show Dir Source # 

Methods

showsPrec :: Int -> Dir -> ShowS #

show :: Dir -> String #

showList :: [Dir] -> ShowS #

Default Dir Source # 

Methods

def :: Dir #

data SplitRule Source #

A SplitRule determines size of each half of the split.

  • Ratio Double sets the split to the given ratio; the double must be between 0 and 1; for example a value of 0.25 sets the first portion of the split to 1/4 of the available space; the other portion takes the remaining 3/4 of the space
  • FromStart Int makes the first half of the split (top/left respectively) the set number of rows or columns respectively, the other half of the split gets the rest.
  • FromEnd Int makes the first half of the split (top/left respectively) the set number of rows or columns respectively, the other half of the split gets the rest.

type Window = BiTree Split View Source #

A tree of windows branched with splits.

data Split Source #

A Split contains info about a the direction and allocation of a split branch.

Constructors

Split 

Fields

Instances

data Views Source #

Extension state storing the window layout

Constructors

Views 

Instances

data View Source #

A View contains info about a viewport; Whether it's selected and which buffer should be displayed.

Constructors

View 

Fields

Instances

data BiTree b l Source #

Constructors

Branch b (BiTree b l) (BiTree b l) 
Leaf l 

Instances

Bifunctor BiTree Source # 

Methods

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

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

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

Functor (BiTree b) Source # 

Methods

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

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

Foldable (BiTree b) Source # 

Methods

fold :: Monoid m => BiTree b m -> m #

foldMap :: Monoid m => (a -> m) -> BiTree b a -> m #

foldr :: (a -> b -> b) -> b -> BiTree b a -> b #

foldr' :: (a -> b -> b) -> b -> BiTree b a -> b #

foldl :: (b -> a -> b) -> b -> BiTree b a -> b #

foldl' :: (b -> a -> b) -> b -> BiTree b a -> b #

foldr1 :: (a -> a -> a) -> BiTree b a -> a #

foldl1 :: (a -> a -> a) -> BiTree b a -> a #

toList :: BiTree b a -> [a] #

null :: BiTree b a -> Bool #

length :: BiTree b a -> Int #

elem :: Eq a => a -> BiTree b a -> Bool #

maximum :: Ord a => BiTree b a -> a #

minimum :: Ord a => BiTree b a -> a #

sum :: Num a => BiTree b a -> a #

product :: Num a => BiTree b a -> a #

Traversable (BiTree b) Source # 

Methods

traverse :: Applicative f => (a -> f b) -> BiTree b a -> f (BiTree b b) #

sequenceA :: Applicative f => BiTree b (f a) -> f (BiTree b a) #

mapM :: Monad m => (a -> m b) -> BiTree b a -> m (BiTree b b) #

sequence :: Monad m => BiTree b (m a) -> m (BiTree b a) #

(Show l, Show b) => Show (BiTree b l) Source # 

Methods

showsPrec :: Int -> BiTree b l -> ShowS #

show :: BiTree b l -> String #

showList :: [BiTree b l] -> ShowS #

Recursive (BiTree a b) Source # 

Methods

project :: BiTree a b -> Base (BiTree a b) (BiTree a b) #

cata :: (Base (BiTree a b) a -> a) -> BiTree a b -> a #

para :: (Base (BiTree a b) (BiTree a b, a) -> a) -> BiTree a b -> a #

gpara :: (Corecursive (BiTree a b), Comonad w) => (forall c. Base (BiTree a b) (w c) -> w (Base (BiTree a b) c)) -> (Base (BiTree a b) (EnvT (BiTree a b) w a) -> a) -> BiTree a b -> a #

prepro :: Corecursive (BiTree a b) => (forall c. Base (BiTree a b) c -> Base (BiTree a b) c) -> (Base (BiTree a b) a -> a) -> BiTree a b -> a #

gprepro :: (Corecursive (BiTree a b), Comonad w) => (forall c. Base (BiTree a b) (w c) -> w (Base (BiTree a b) c)) -> (forall c. Base (BiTree a b) c -> Base (BiTree a b) c) -> (Base (BiTree a b) (w a) -> a) -> BiTree a b -> a #

Corecursive (BiTree a b) Source # 

Methods

embed :: Base (BiTree a b) (BiTree a b) -> BiTree a b #

ana :: (a -> Base (BiTree a b) a) -> a -> BiTree a b #

apo :: (a -> Base (BiTree a b) (Either (BiTree a b) a)) -> a -> BiTree a b #

postpro :: Recursive (BiTree a b) => (forall c. Base (BiTree a b) c -> Base (BiTree a b) c) -> (a -> Base (BiTree a b) a) -> a -> BiTree a b #

gpostpro :: (Recursive (BiTree a b), Monad m) => (forall c. m (Base (BiTree a b) c) -> Base (BiTree a b) (m c)) -> (forall c. Base (BiTree a b) c -> Base (BiTree a b) c) -> (a -> Base (BiTree a b) (m a)) -> a -> BiTree a b #

type Base (BiTree a b) Source # 
type Base (BiTree a b) = BiTreeF a b

data BiTreeF b l r Source #

Constructors

BranchF b r r 
LeafF l 

Instances

Functor (BiTreeF b l) Source # 

Methods

fmap :: (a -> b) -> BiTreeF b l a -> BiTreeF b l b #

(<$) :: a -> BiTreeF b l b -> BiTreeF b l a #

(Show l, Show r, Show b) => Show (BiTreeF b l r) Source # 

Methods

showsPrec :: Int -> BiTreeF b l r -> ShowS #

show :: BiTreeF b l r -> String #

showList :: [BiTreeF b l r] -> ShowS #