yi-0.6.5.0: The Haskell-Scriptable Editor

Safe HaskellSafe-Infered

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

orientation :: !Orientation

Orientation

Orientation

wins :: [(Layout a, RelativeSize)]

The layout stack, with the given weights TODO: fix strictness for stack (it's still lazy)

Pair 

Fields

orientation :: !Orientation

Orientation

Orientation

divPos :: !DividerPosition

Initial position of the divider

divRef :: !DividerRef

Index of the divider (for updating the divider position)

pairFst :: !(Layout a)

Upper of of the pair

pairSnd :: !(Layout a)

Lower of the pair

Instances

Functor Layout 
Typeable1 Layout 
Eq a => Eq (Layout a) 
Show a => Show (Layout a) 
Initializable a => Initializable (Layout a)

The initial layout consists of a single window

Transposable (Layout a) 

type DividerPosition = DoubleSource

Divider position, in the range (0,1)

type DividerRef = IntSource

Divider reference

type RelativeSize = DoubleSource

Relative sizes, for Stack

dividerPositionA :: DividerRef -> Accessor (Layout a) DividerPositionSource

Accessor for the DividerPosition with given reference

Layout managers

The interface

class (Typeable m, Eq m) => LayoutManager m whereSource

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

Methods

pureLayout :: m -> Layout a -> [a] -> Layout aSource

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 -> StringSource

Describe the layout in a form suitable for the user.

nextVariant :: m -> mSource

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

previousVariant :: m -> mSource

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

data AnyLayoutManager Source

Existential wrapper for Layout

Constructors

forall m . LayoutManager m => AnyLayoutManager !m 

layoutManagerSameType :: AnyLayoutManager -> AnyLayoutManager -> BoolSource

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

Standard managers

wide :: AnyLayoutManagerSource

Windows placed on top of one another, equally spaced

tall :: AnyLayoutManagerSource

Windows placed side-by-side, equally spaced.

slidyTall :: AnyLayoutManagerSource

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

slidyWide :: AnyLayoutManagerSource

Transposed version of slidyTall

hPairNStack :: Int -> AnyLayoutManagerSource

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

vPairNStack :: Int -> AnyLayoutManagerSource

Transposed version of hPairNStack.

Utility functions

Layouts as rectangles

data Rectangle Source

A general bounding box

Constructors

Rectangle 

Transposing things

class Transposable r whereSource

Things with orientations which can be flipped

Methods

transpose :: r -> rSource

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 aSource

Special case of stack with all RelativeSizes equal.