yi-core-0.14.1: Yi editor core library

Safe HaskellNone
LanguageHaskell2010

Yi.Layout

Contents

Description

This module defines the layout manager interface (see LayoutManager). To desgin a new layout manager, just make an instance of this class.

Synopsis

Concrete layouts

data Layout a Source #

UI-agnostic layout schema. The basic constructs are (horizontal/vertical) stacks with fixed ratios between window sizes; and (horizontal/vertical) pairs with a slider in between (if available).

Constructors

SingleWindow a 
Stack 

Fields

Pair 

Fields

Instances

Functor Layout Source # 

Methods

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

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

Eq a => Eq (Layout a) Source # 

Methods

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

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

Show a => Show (Layout a) Source # 

Methods

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

show :: Layout a -> String #

showList :: [Layout a] -> ShowS #

Default a => Default (Layout a) Source #

The def layout consists of a single window

Methods

def :: Layout a #

Transposable (Layout a) Source # 

Methods

transpose :: Layout a -> Layout a Source #

type DividerPosition = Double Source #

Divider position, in the range (0,1)

type DividerRef = Int Source #

Divider reference

type RelativeSize = Double Source #

Relative sizes, for Stack

dividerPositionA :: DividerRef -> Lens' (Layout a) DividerPosition Source #

Accessor for the DividerPosition with given reference

findDivider :: Eq a => Maybe a -> Layout a -> Maybe DividerRef Source #

Find the divider nearest to a given window, or just the first one in case the argument is Nothing

Layout managers

The interface

class (Typeable m, Eq m) => LayoutManager m where Source #

The type of layout managers. See the layout managers tall, hPairNStack and slidyTall for some example implementations.

Minimal complete definition

pureLayout, describeLayout

Methods

pureLayout :: m -> Layout a -> [a] -> Layout a Source #

Given the old layout and the new list of windows, construct a layout for the new list of windows.

If the layout manager uses sliding dividers, then a user will expect that most of these dividers don't move when adding a new window. It is the layout manager's responsibility to ensure that this is the case, and this is the purpose of the Layout a argument.

The old layout may come from a different layout manager, in which case the layout manager is free to ignore it.

describeLayout :: m -> String Source #

Describe the layout in a form suitable for the user.

nextVariant :: m -> m Source #

Cycles to the next variant, if there is one (the default is id)

previousVariant :: m -> m Source #

Cycles to the previous variant, if there is one (the default is id

layoutManagerSameType :: AnyLayoutManager -> AnyLayoutManager -> Bool Source #

True if the internal layout managers have the same type (but are not necessarily equal).

Standard managers

wide :: AnyLayoutManager Source #

Windows placed on top of one another, equally spaced

tall :: AnyLayoutManager Source #

Windows placed side-by-side, equally spaced.

slidyTall :: AnyLayoutManager Source #

Tall windows, arranged in a balanced binary tree with sliders in between them.

slidyWide :: AnyLayoutManager Source #

Transposed version of slidyTall

hPairNStack :: Int -> AnyLayoutManager Source #

n windows on the left; stack of windows on the right.

vPairNStack :: Int -> AnyLayoutManager Source #

Transposed version of hPairNStack.

Utility functions

Layouts as rectangles

data Rectangle Source #

A general bounding box

Constructors

Rectangle 

type HasNeighborWest = Bool Source #

Used by the vty frontend to draw vertical separators

Transposing things

class Transposable r where Source #

Things with orientations which can be flipped

Minimal complete definition

transpose

Methods

transpose :: r -> r Source #

newtype Transposed lm Source #

Same as lm, but with all Orientations transposed. See slidyWide for an example of its use.

Constructors

Transposed lm 

DividerRef combinators

It is tedious and error-prone for LayoutManagers to assign DividerRefs themselves. Better is to use these monadic smart constructors for Layout. For example, the layout

Pair Horizontal 0.5 0 (Pair Vertical 0.5 1 (SingleWindow w1) (SingleWindow w2)) (SingleWindow w3)

could be with the combinators below as

runLayoutM $ pair Horizontal 0.5 (pair Vertical 0.5 (singleWindow w1) (singleWindow w2)) (singleWindow w3)

These combinators do will also ensure strictness of the wins field of Stack. They also tidy up and do some error checking: length-1 stacks are removed (they are unnecessary); length-0 stacks raise errors.

data LayoutM a Source #

A 'Layout a' wrapped in a state monad for tracking DividerRefs. This type is not itself a monad, but should rather be thought of as a DividerRef-free version of the Layout type.

evenStack :: Orientation -> [LayoutM a] -> LayoutM a Source #

Special case of stack with all RelativeSizes equal.