| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
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.
- data Layout a
- = SingleWindow a
 - | Stack { 
- orientation :: !Orientation
 - wins :: [(Layout a, RelativeSize)]
 
 - | Pair { 
- orientation :: !Orientation
 - divPos :: !DividerPosition
 - divRef :: !DividerRef
 - pairFst :: !(Layout a)
 - pairSnd :: !(Layout a)
 
 
 - data Orientation
 - type DividerPosition = Double
 - type DividerRef = Int
 - type RelativeSize = Double
 - dividerPositionA :: DividerRef -> Lens' (Layout a) DividerPosition
 - class (Typeable m, Eq m) => LayoutManager m where
- pureLayout :: m -> Layout a -> [a] -> Layout a
 - describeLayout :: m -> String
 - nextVariant :: m -> m
 - previousVariant :: m -> m
 
 - data AnyLayoutManager = forall m . LayoutManager m => AnyLayoutManager !m
 - layoutManagerSameType :: AnyLayoutManager -> AnyLayoutManager -> Bool
 - wide :: AnyLayoutManager
 - tall :: AnyLayoutManager
 - slidyTall :: AnyLayoutManager
 - slidyWide :: AnyLayoutManager
 - hPairNStack :: Int -> AnyLayoutManager
 - vPairNStack :: Int -> AnyLayoutManager
 - data Rectangle = Rectangle {}
 - layoutToRectangles :: Rectangle -> Layout a -> [(a, Rectangle)]
 - class Transposable r where
- transpose :: r -> r
 
 - newtype Transposed lm = Transposed lm
 - data LayoutM a
 - pair :: Orientation -> DividerPosition -> LayoutM a -> LayoutM a -> LayoutM a
 - singleWindow :: a -> LayoutM a
 - stack :: Orientation -> [(LayoutM a, RelativeSize)] -> LayoutM a
 - evenStack :: Orientation -> [LayoutM a] -> LayoutM a
 - runLayoutM :: LayoutM a -> Layout a
 
Concrete layouts
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 
  | |
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
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
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
Instances
data AnyLayoutManager Source
Existential wrapper for Layout
Constructors
| forall m . LayoutManager m => AnyLayoutManager !m | 
Instances
| Eq AnyLayoutManager | |
| Default AnyLayoutManager | The default layout is   | 
| LayoutManager AnyLayoutManager | |
| Typeable * AnyLayoutManager | 
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
A general bounding box
Constructors
| Rectangle | |
layoutToRectangles :: Rectangle -> Layout a -> [(a, Rectangle)] Source
Transposing things
newtype Transposed lm Source
Same as lm, but with all Orientations transposed. See slidyWide for an example of its use.
Constructors
| Transposed lm | 
Instances
| Eq lm => Eq (Transposed lm) | |
| LayoutManager lm => LayoutManager (Transposed lm) | |
| Typeable (* -> *) Transposed | 
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
PairHorizontal0.5 0 (PairVertical0.5 1 (SingleWindoww1) (SingleWindoww2)) (SingleWindoww3)
could be with the combinators below as
runLayoutM$pairHorizontal0.5 (pairVertical0.5 (singleWindoww1) (singleWindoww2)) (singleWindoww3)
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.
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.
pair :: Orientation -> DividerPosition -> LayoutM a -> LayoutM a -> LayoutM a Source
singleWindow :: a -> LayoutM a Source
stack :: Orientation -> [(LayoutM a, RelativeSize)] -> LayoutM a Source
evenStack :: Orientation -> [LayoutM a] -> LayoutM a Source
Special case of stack with all RelativeSizes equal.
runLayoutM :: LayoutM a -> Layout a Source