summaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
authorMalebria <malebria@riseup.net>2008-06-01 23:25:15 +0200
committerMalebria <malebria@riseup.net>2008-06-01 23:25:15 +0200
commit9f5290a33599230facde1153bb3708e313354c4d (patch)
tree027bfbc9ef65400909966089c27bbb24d5cb0e1d
parent204714ce5e44752f2b2115650839c846e8e96f32 (diff)
downloadmetatile-9f5290a33599230facde1153bb3708e313354c4d.tar
metatile-9f5290a33599230facde1153bb3708e313354c4d.zip
Haddock links
darcs-hash:20080601212515-1ef02-00edd6567c840d7fec8ee7ed085b3cd2655ad6e3
-rw-r--r--XMonad/Core.hs28
-rw-r--r--XMonad/ManageHook.hs6
-rw-r--r--XMonad/Operations.hs14
-rw-r--r--XMonad/StackSet.hs42
4 files changed, 45 insertions, 45 deletions
diff --git a/XMonad/Core.hs b/XMonad/Core.hs
index e59d3e7..1bc289a 100644
--- a/XMonad/Core.hs
+++ b/XMonad/Core.hs
@@ -13,7 +13,7 @@
-- Stability : unstable
-- Portability : not portable, uses cunning newtype deriving
--
--- The X monad, a state monad transformer over IO, for the window
+-- The 'X' monad, a state monad transformer over 'IO', for the window
-- manager state, and support routines.
--
-----------------------------------------------------------------------------
@@ -107,13 +107,13 @@ data ScreenDetail = SD { screenRect :: !Rectangle } deriving (Eq,Show, Read)
------------------------------------------------------------------------
--- | The X monad, ReaderT and StateT transformers over IO
+-- | The X monad, 'ReaderT' and 'StateT' transformers over 'IO'
-- encapsulating the window manager configuration and state,
-- respectively.
--
-- Dynamic components may be retrieved with 'get', static components
-- with 'ask'. With newtype deriving we get readers and state monads
--- instantiated on XConf and XState automatically.
+-- instantiated on 'XConf' and 'XState' automatically.
--
newtype X a = X (ReaderT XConf (StateT XState IO) a)
#ifndef __HADDOCK__
@@ -141,12 +141,12 @@ instance Monoid a => Monoid (Query a) where
mempty = return mempty
mappend = liftM2 mappend
--- | Run the X monad, given a chunk of X monad code, and an initial state
+-- | Run the 'X' monad, given a chunk of 'X' monad code, and an initial state
-- Return the result, and final state
runX :: XConf -> XState -> X a -> IO (a, XState)
runX c st (X a) = runStateT (runReaderT a c) st
--- | Run in the X monad, and in case of exception, and catch it and log it
+-- | Run in the 'X' monad, and in case of exception, and catch it and log it
-- to stderr, and run the error case.
catchX :: X a -> X a -> X a
catchX job errcase = do
@@ -159,7 +159,7 @@ catchX job errcase = do
return a
-- | Execute the argument, catching all exceptions. Either this function or
--- catchX should be used at all callsites of user customized code.
+-- 'catchX' should be used at all callsites of user customized code.
userCode :: X () -> X ()
userCode a = catchX (a >> return ()) (return ())
@@ -328,11 +328,11 @@ instance Message LayoutMessages
-- ---------------------------------------------------------------------
-- | General utilities
--
--- Lift an IO action into the X monad
+-- Lift an 'IO' action into the 'X' monad
io :: MonadIO m => IO a -> m a
io = liftIO
--- | Lift an IO action into the X monad. If the action results in an IO
+-- | Lift an 'IO' action into the 'X' monad. If the action results in an 'IO'
-- exception, log the exception to stderr and continue normal execution.
catchIO :: MonadIO m => IO () -> m ()
catchIO f = io (f `catch` \e -> hPrint stderr e >> hFlush stderr)
@@ -341,7 +341,7 @@ catchIO f = io (f `catch` \e -> hPrint stderr e >> hFlush stderr)
spawn :: MonadIO m => String -> m ()
spawn x = doubleFork $ executeFile "/bin/sh" False ["-c", x] Nothing
--- | Double fork and execute an IO action (usually one of the exec family of
+-- | Double fork and execute an 'IO' action (usually one of the exec family of
-- functions)
doubleFork :: MonadIO m => IO () -> m ()
doubleFork m = io $ do
@@ -351,7 +351,7 @@ doubleFork m = io $ do
getProcessStatus True False pid
return ()
--- | This is basically a map function, running a function in the X monad on
+-- | This is basically a map function, running a function in the 'X' monad on
-- each workspace with the output of that function being the modified workspace.
runOnWorkspaces :: (WindowSpace -> X WindowSpace) -> X ()
runOnWorkspaces job = do
@@ -368,7 +368,7 @@ getXMonadDir = io $ getAppUserDataDirectory "xmonad"
-- | 'recompile force', recompile @~\/.xmonad\/xmonad.hs@ when any of the
-- following apply:
--
--- * force is True
+-- * force is 'True'
--
-- * the xmonad executable does not exist
--
@@ -380,7 +380,7 @@ getXMonadDir = io $ getAppUserDataDirectory "xmonad"
-- GHC indicates failure with a non-zero exit code, an xmessage displaying
-- that file is spawned.
--
--- False is returned if there are compilation errors.
+-- 'False' is returned if there are compilation errors.
--
recompile :: MonadIO m => Bool -> m Bool
recompile force = io $ do
@@ -416,11 +416,11 @@ recompile force = io $ do
whenJust :: Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust mg f = maybe (return ()) f mg
--- | Conditionally run an action, using a X event to decide
+-- | Conditionally run an action, using a 'X' event to decide
whenX :: X Bool -> X () -> X ()
whenX a f = a >>= \b -> when b f
--- | A 'trace' for the X monad. Logs a string to stderr. The result may
+-- | A 'trace' for the 'X' monad. Logs a string to stderr. The result may
-- be found in your .xsession-errors file
trace :: MonadIO m => String -> m ()
trace = io . hPutStrLn stderr
diff --git a/XMonad/ManageHook.hs b/XMonad/ManageHook.hs
index a0bbb4c..f2478b2 100644
--- a/XMonad/ManageHook.hs
+++ b/XMonad/ManageHook.hs
@@ -55,11 +55,11 @@ q =? x = fmap (== x) q
infixr 3 <&&>, <||>
--- | '&&' lifted to a Monad.
+-- | '&&' lifted to a 'Monad'.
(<&&>) :: Monad m => m Bool -> m Bool -> m Bool
(<&&>) = liftM2 (&&)
--- | '||' lifted to a Monad.
+-- | '||' lifted to a 'Monad'.
(<||>) :: Monad m => m Bool -> m Bool -> m Bool
(<||>) = liftM2 (||)
@@ -86,7 +86,7 @@ resource = appName
className :: Query String
className = ask >>= (\w -> liftX $ withDisplay $ \d -> fmap resClass $ io $ getClassHint d w)
--- | A query that can return an arbitrary X property of type String,
+-- | A query that can return an arbitrary X property of type 'String',
-- identified by name.
stringProperty :: String -> Query String
stringProperty p = ask >>= (\w -> liftX $ withDisplay $ \d -> fmap (fromMaybe "") $ getStringProperty d w p)
diff --git a/XMonad/Operations.hs b/XMonad/Operations.hs
index 4c2623b..944c592 100644
--- a/XMonad/Operations.hs
+++ b/XMonad/Operations.hs
@@ -210,7 +210,7 @@ setInitialProperties w = asks normalBorder >>= \nb -> withDisplay $ \d -> do
io $ setWindowBorder d w nb
-- | refresh. Render the currently visible workspaces, as determined by
--- the StackSet. Also, set focus to the focused window.
+-- the 'StackSet'. Also, set focus to the focused window.
--
-- This is our 'view' operation (MVC), in that it pretty prints our model
-- with X calls.
@@ -239,7 +239,7 @@ tileWindow w r = withDisplay $ \d -> do
-- ---------------------------------------------------------------------
--- | Returns True if the first rectangle is contained within, but not equal
+-- | Returns 'True' if the first rectangle is contained within, but not equal
-- to the second.
containedIn :: Rectangle -> Rectangle -> Bool
containedIn r1@(Rectangle x1 y1 w1 h1) r2@(Rectangle x2 y2 w2 h2)
@@ -318,7 +318,7 @@ setFocusX w = withWindowSet $ \ws -> do
------------------------------------------------------------------------
-- Message handling
--- | Throw a message to the current LayoutClass possibly modifying how we
+-- | Throw a message to the current 'LayoutClass' possibly modifying how we
-- layout the windows, then refresh.
sendMessage :: Message a => a -> X ()
sendMessage a = do
@@ -358,15 +358,15 @@ setLayout l = do
------------------------------------------------------------------------
-- Utilities
--- | Return workspace visible on screen 'sc', or Nothing.
+-- | Return workspace visible on screen 'sc', or 'Nothing'.
screenWorkspace :: ScreenId -> X (Maybe WorkspaceId)
screenWorkspace sc = withWindowSet $ return . W.lookupWorkspace sc
--- | Apply an X operation to the currently focused window, if there is one.
+-- | Apply an 'X' operation to the currently focused window, if there is one.
withFocused :: (Window -> X ()) -> X ()
withFocused f = withWindowSet $ \w -> whenJust (W.peek w) f
--- | True if window is under management by us
+-- | 'True' if window is under management by us
isClient :: Window -> X Bool
isClient w = withWindowSet $ return . W.member w
@@ -383,7 +383,7 @@ cleanMask km = do
nlm <- asks (numlockMask . config)
return (complement (nlm .|. lockMask) .&. km)
--- | Get the Pixel value for a named color
+-- | Get the 'Pixel' value for a named color
initColor :: Display -> String -> IO (Maybe Pixel)
initColor dpy c = C.handle (\_ -> return Nothing) $
(Just . color_pixel . fst) <$> allocNamedColor dpy colormap c
diff --git a/XMonad/StackSet.hs b/XMonad/StackSet.hs
index 7674a44..62c3c34 100644
--- a/XMonad/StackSet.hs
+++ b/XMonad/StackSet.hs
@@ -111,7 +111,7 @@ import qualified Data.Map as M (Map,insert,delete,empty)
-- receive keyboard events), other workspaces may be passively
-- viewable. We thus need to track which virtual workspaces are
-- associated (viewed) on which physical screens. To keep track of
--- this, StackSet keeps separate lists of visible but non-focused
+-- this, 'StackSet' keeps separate lists of visible but non-focused
-- workspaces, and non-visible workspaces.
-- $focus
@@ -202,7 +202,7 @@ new _ _ _ = abort "non-positive argument to StackSet.new"
-- |
-- /O(w)/. Set focus to the workspace with index \'i\'.
--- If the index is out of range, return the original StackSet.
+-- If the index is out of range, return the original 'StackSet'.
--
-- Xinerama: If the workspace is not visible on any Xinerama screen, it
-- becomes the current screen. If it is in the visible list, it becomes
@@ -252,7 +252,7 @@ greedyView w ws
-- $xinerama
-- | Find the tag of the workspace visible on Xinerama screen 'sc'.
--- Nothing if screen is out of bounds.
+-- 'Nothing' if screen is out of bounds.
lookupWorkspace :: Eq s => s -> StackSet i l a s sd -> Maybe i
lookupWorkspace sc w = listToMaybe [ tag i | Screen i s _ <- current w : visible w, s == sc ]
@@ -269,7 +269,7 @@ with :: b -> (Stack a -> b) -> StackSet i l a s sd -> b
with dflt f = maybe dflt f . stack . workspace . current
-- |
--- Apply a function, and a default value for Nothing, to modify the current stack.
+-- Apply a function, and a default value for 'Nothing', to modify the current stack.
--
modify :: Maybe (Stack a) -> (Stack a -> Maybe (Stack a)) -> StackSet i l a s sd -> StackSet i l a s sd
modify d f s = s { current = (current s)
@@ -284,13 +284,13 @@ modify' f = modify Nothing (Just . f)
-- |
-- /O(1)/. Extract the focused element of the current stack.
--- Return Just that element, or Nothing for an empty stack.
+-- Return 'Just' that element, or 'Nothing' for an empty stack.
--
peek :: StackSet i l a s sd -> Maybe a
peek = with Nothing (return . focus)
-- |
--- /O(n)/. Flatten a Stack into a list.
+-- /O(n)/. Flatten a 'Stack' into a list.
--
integrate :: Stack a -> [a]
integrate (Stack x l r) = reverse l ++ x : r
@@ -310,7 +310,7 @@ differentiate (x:xs) = Just $ Stack x [] xs
-- |
-- /O(n)/. 'filter p s' returns the elements of 's' such that 'p' evaluates to
--- True. Order is preserved, and focus moves as described for 'delete'.
+-- 'True'. Order is preserved, and focus moves as described for 'delete'.
--
filter :: (a -> Bool) -> Stack a -> Maybe (Stack a)
filter p (Stack f ls rs) = case L.filter p (f:rs) of
@@ -368,15 +368,15 @@ focusWindow w s | Just w == peek s = s
n <- findTag w s
return $ until ((Just w ==) . peek) focusUp (view n s)
--- | Get a list of all screens in the StackSet.
+-- | Get a list of all screens in the 'StackSet'.
screens :: StackSet i l a s sd -> [Screen i l a s sd]
screens s = current s : visible s
--- | Get a list of all workspaces in the StackSet.
+-- | Get a list of all workspaces in the 'StackSet'.
workspaces :: StackSet i l a s sd -> [Workspace i l a]
workspaces s = workspace (current s) : map workspace (visible s) ++ hidden s
--- | Get a list of all windows in the StackSet in no particular order
+-- | Get a list of all windows in the 'StackSet' in no particular order
allWindows :: Eq a => StackSet i l a s sd -> [a]
allWindows = L.nub . concatMap (integrate' . stack) . workspaces
@@ -384,11 +384,11 @@ allWindows = L.nub . concatMap (integrate' . stack) . workspaces
currentTag :: StackSet i l a s sd -> i
currentTag = tag . workspace . current
--- | Is the given tag present in the StackSet?
+-- | Is the given tag present in the 'StackSet'?
tagMember :: Eq i => i -> StackSet i l a s sd -> Bool
tagMember t = elem t . map tag . workspaces
--- | Rename a given tag if present in the StackSet.
+-- | Rename a given tag if present in the 'StackSet'.
renameTag :: Eq i => i -> i -> StackSet i l a s sd -> StackSet i l a s sd
renameTag o n = mapWorkspace rename
where rename w = if tag w == o then w { tag = n } else w
@@ -403,27 +403,27 @@ ensureTags l allt st = et allt (map tag (workspaces st) \\ allt) st
et (i:is) [] s = et is [] (s { hidden = Workspace i l Nothing : hidden s })
et (i:is) (r:rs) s = et is rs $ renameTag r i s
--- | Map a function on all the workspaces in the StackSet.
+-- | Map a function on all the workspaces in the 'StackSet'.
mapWorkspace :: (Workspace i l a -> Workspace i l a) -> StackSet i l a s sd -> StackSet i l a s sd
mapWorkspace f s = s { current = updScr (current s)
, visible = map updScr (visible s)
, hidden = map f (hidden s) }
where updScr scr = scr { workspace = f (workspace scr) }
--- | Map a function on all the layouts in the StackSet.
+-- | Map a function on all the layouts in the 'StackSet'.
mapLayout :: (l -> l') -> StackSet i l a s sd -> StackSet i l' a s sd
mapLayout f (StackSet v vs hs m) = StackSet (fScreen v) (map fScreen vs) (map fWorkspace hs) m
where
fScreen (Screen ws s sd) = Screen (fWorkspace ws) s sd
fWorkspace (Workspace t l s) = Workspace t (f l) s
--- | /O(n)/. Is a window in the StackSet?
+-- | /O(n)/. Is a window in the 'StackSet'?
member :: Eq a => a -> StackSet i l a s sd -> Bool
member a s = isJust (findTag a s)
-- | /O(1) on current window, O(n) in general/.
--- Return Just the workspace tag of the given window, or Nothing
--- if the window is not in the StackSet.
+-- Return 'Just' the workspace tag of the given window, or 'Nothing'
+-- if the window is not in the 'StackSet'.
findTag :: Eq a => a -> StackSet i l a s sd -> Maybe i
findTag a s = listToMaybe
[ tag w | w <- workspaces s, has a (stack w) ]
@@ -458,13 +458,13 @@ insertUp a s = if member a s then s else insert
-- /O(1) on current window, O(n) in general/. Delete window 'w' if it exists.
-- There are 4 cases to consider:
--
--- * delete on an Nothing workspace leaves it Nothing
+-- * delete on an 'Nothing' workspace leaves it Nothing
--
-- * otherwise, try to move focus to the down
--
-- * otherwise, try to move focus to the up
--
--- * otherwise, you've got an empty workspace, becomes Nothing
+-- * otherwise, you've got an empty workspace, becomes 'Nothing'
--
-- Behaviour with respect to the master:
--
@@ -476,7 +476,7 @@ delete :: (Ord a, Eq s) => a -> StackSet i l a s sd -> StackSet i l a s sd
delete w = sink w . delete' w
-- | Only temporarily remove the window from the stack, thereby not destroying special
--- information saved in the Stackset
+-- information saved in the 'Stackset'
delete' :: (Eq a, Eq s) => a -> StackSet i l a s sd -> StackSet i l a s sd
delete' w s = s { current = removeFromScreen (current s)
, visible = map removeFromScreen (visible s)
@@ -487,7 +487,7 @@ delete' w s = s { current = removeFromScreen (current s)
------------------------------------------------------------------------
-- | Given a window, and its preferred rectangle, set it as floating
--- A floating window should already be managed by the StackSet.
+-- A floating window should already be managed by the 'StackSet'.
float :: Ord a => a -> RationalRect -> StackSet i l a s sd -> StackSet i l a s sd
float w r s = s { floating = M.insert w r (floating s) }