From 96d7417e6d3921601cd0549e550ab3a478c15c0c Mon Sep 17 00:00:00 2001 From: Brent Yorgey Date: Tue, 11 Mar 2008 17:07:27 +0100 Subject: update documentation darcs-hash:20080311160727-bd4d7-05229354077a443abab79de16b60ac32728813a3 --- XMonad/Core.hs | 89 ++++++++++++++++++++++++++++++++++++++++------------------ 1 file changed, 62 insertions(+), 27 deletions(-) (limited to 'XMonad/Core.hs') diff --git a/XMonad/Core.hs b/XMonad/Core.hs index 32fc234..c32678e 100644 --- a/XMonad/Core.hs +++ b/XMonad/Core.hs @@ -191,61 +191,95 @@ atom_WM_DELETE_WINDOW = getAtom "WM_DELETE_WINDOW" atom_WM_STATE = getAtom "WM_STATE" ------------------------------------------------------------------------ --- | LayoutClass handling. See particular instances in Operations.hs +-- LayoutClass handling. See particular instances in Operations.hs --- | An existential type that can hold any object that is in Read and LayoutClass. +-- | An existential type that can hold any object that is in 'Read' +-- and 'LayoutClass'. data Layout a = forall l. (LayoutClass l a, Read (l a)) => Layout (l a) -- | Using the 'Layout' as a witness, parse existentially wrapped windows --- from a 'String' +-- from a 'String'. readsLayout :: Layout a -> String -> [(Layout a, String)] readsLayout (Layout l) s = [(Layout (asTypeOf x l), rs) | (x, rs) <- reads s] --- | Every layout must be an instance of LayoutClass, which defines +-- | Every layout must be an instance of 'LayoutClass', which defines -- the basic layout operations along with a sensible default for each. -- +-- Minimal complete definition: +-- +-- * 'runLayout' || (('doLayout' || 'pureLayout') && 'emptyLayout'), and +-- +-- * 'handleMessage' || 'pureMessage' +-- +-- You should also strongly consider implementing 'description', +-- although it is not required. +-- +-- Note that any code which /uses/ 'LayoutClass' methods should only +-- ever call 'runLayout', 'handleMessage', and 'description'! In +-- other words, the only calls to 'doLayout', 'pureMessage', and other +-- such methods should be from the default implementations of +-- 'runLayout', 'handleMessage', and so on. This ensures that the +-- proper methods will be used, regardless of the particular methods +-- that any 'LayoutClass' instance chooses to define. class Show (layout a) => LayoutClass layout a where - -- | This calls doLayout if there are any windows to be laid out, and - -- emptyLayout otherwise. + -- | By default, 'runLayout' calls 'doLayout' if there are any + -- windows to be laid out, and 'emptyLayout' otherwise. Most + -- instances of 'LayoutClass' probably do not need to implement + -- 'runLayout'; it is only useful for layouts which wish to make + -- use of more of the 'Workspace' information (for example, + -- "XMonad.Layout.PerWorkspace"). runLayout :: Workspace WorkspaceId (layout a) a -> Rectangle -> X ([(a, Rectangle)], Maybe (layout a)) runLayout (Workspace _ l ms) r = maybe (emptyLayout l r) (doLayout l r) ms - -- | Given a Rectangle in which to place the windows, and a Stack + -- | Given a 'Rectangle' in which to place the windows, and a 'Stack' -- of windows, return a list of windows and their corresponding -- Rectangles. If an element is not given a Rectangle by -- 'doLayout', then it is not shown on screen. The order of -- windows in this list should be the desired stacking order. -- - -- Also return a modified layout, if this layout needs to be modified - -- (e.g. if we keep track of the windows we have displayed). + -- Also possibly return a modified layout (by returning @Just + -- newLayout@), if this layout needs to be modified (e.g. if it + -- keeps track of some sort of state). Return @Nothing@ if the + -- layout does not need to be modified. + -- + -- Layouts which do not need access to the 'X' monad ('IO', window + -- manager state, or configuration) and do not keep track of their + -- own state should implement 'pureLayout' instead of 'doLayout'. doLayout :: layout a -> Rectangle -> Stack a -> X ([(a, Rectangle)], Maybe (layout a)) doLayout l r s = return (pureLayout l r s, Nothing) - -- | This is a pure version of doLayout, for cases where we don't need - -- access to the X monad to determine how to layout the windows, and - -- we don't need to modify our layout itself. + -- | This is a pure version of 'doLayout', for cases where we + -- don't need access to the 'X' monad to determine how to lay out + -- the windows, and we don't need to modify the layout itself. pureLayout :: layout a -> Rectangle -> Stack a -> [(a, Rectangle)] pureLayout _ r s = [(focus s, r)] - -- | 'emptyLayout' is called when there is no window. + -- | 'emptyLayout' is called when there are no windows. emptyLayout :: layout a -> Rectangle -> X ([(a, Rectangle)], Maybe (layout a)) emptyLayout _ _ = return ([], Nothing) - -- | 'handleMessage' performs message handling for that layout. If - -- 'handleMessage' returns Nothing, then the layout did not respond to - -- that message and the screen is not refreshed. Otherwise, 'handleMessage' - -- returns an updated 'Layout' and the screen is refreshed. + -- | 'handleMessage' performs message handling. If + -- 'handleMessage' returns @Nothing@, then the layout did not + -- respond to the message and the screen is not refreshed. + -- Otherwise, 'handleMessage' returns an updated layout and the + -- screen is refreshed. + -- + -- Layouts which do not need access to the 'X' monad to decide how + -- to handle messages should implement 'pureMessage' instead of + -- 'handleMessage'. handleMessage :: layout a -> SomeMessage -> X (Maybe (layout a)) handleMessage l = return . pureMessage l - -- | Respond to a message by (possibly) changing our layout, but taking - -- no other action. If the layout changes, the screen will be refreshed. + -- | Respond to a message by (possibly) changing our layout, but + -- taking no other action. If the layout changes, the screen will + -- be refreshed. pureMessage :: layout a -> SomeMessage -> Maybe (layout a) pureMessage _ _ = Nothing - -- | This should be a human-readable string that is used when selecting - -- layouts by name. + -- | This should be a human-readable string that is used when + -- selecting layouts by name. The default implementation is + -- 'show', which is in some cases a poor default. description :: layout a -> String description = show @@ -258,29 +292,30 @@ instance LayoutClass Layout Window where instance Show (Layout a) where show (Layout l) = show l --- | Based on ideas in /An Extensible Dynamically-Typed Hierarchy of Exceptions/, --- Simon Marlow, 2006. Use extensible messages to the handleMessage handler. +-- | Based on ideas in /An Extensible Dynamically-Typed Hierarchy of +-- Exceptions/, Simon Marlow, 2006. Use extensible messages to the +-- 'handleMessage' handler. -- -- User-extensible messages must be a member of this class. -- class Typeable a => Message a -- | --- A wrapped value of some type in the Message class. +-- A wrapped value of some type in the 'Message' class. -- data SomeMessage = forall a. Message a => SomeMessage a -- | --- And now, unwrap a given, unknown Message type, performing a (dynamic) +-- And now, unwrap a given, unknown 'Message' type, performing a (dynamic) -- type check on the result. -- fromMessage :: Message m => SomeMessage -> Maybe m fromMessage (SomeMessage m) = cast m --- | X Events are valid Messages +-- X Events are valid Messages. instance Message Event --- | LayoutMessages are core messages that all layouts (especially stateful +-- | 'LayoutMessages' are core messages that all layouts (especially stateful -- layouts) should consider handling. data LayoutMessages = Hide -- ^ sent when a layout becomes non-visible | ReleaseResources -- ^ sent when xmonad is exiting or restarting -- cgit v1.2.3