aboutsummaryrefslogtreecommitdiffstats
path: root/XMonad
diff options
context:
space:
mode:
authorAdam Vogt <vogt.adam@gmail.com>2010-10-23 21:57:55 +0200
committerAdam Vogt <vogt.adam@gmail.com>2010-10-23 21:57:55 +0200
commit1b3327dc7cd7f87aa8dee335889fde734a8ac48b (patch)
tree3bb4469e2a02c6c91d3d94c4702ec6c6d5e24b79 /XMonad
parent5bf2f254461743db248125f09144100d9279da4a (diff)
downloadXMonadContrib-1b3327dc7cd7f87aa8dee335889fde734a8ac48b.tar.gz
XMonadContrib-1b3327dc7cd7f87aa8dee335889fde734a8ac48b.tar.xz
XMonadContrib-1b3327dc7cd7f87aa8dee335889fde734a8ac48b.zip
Export types to reduce haddock warnings.
Ignore-this: 1cac9202784711ce0fc902d14543bab0 darcs-hash:20101023195755-1499c-57c41357d20cbf0d57522ce99bdbfff7b686ed52.gz
Diffstat (limited to 'XMonad')
-rw-r--r--XMonad/Actions/DynamicWorkspaceGroups.hs4
-rw-r--r--XMonad/Actions/DynamicWorkspaces.hs9
-rw-r--r--XMonad/Actions/FloatKeys.hs4
-rw-r--r--XMonad/Actions/Search.hs5
-rw-r--r--XMonad/Actions/TagWindows.hs3
-rw-r--r--XMonad/Actions/WindowNavigation.hs2
-rw-r--r--XMonad/Actions/WorkspaceCursors.hs5
-rw-r--r--XMonad/Actions/WorkspaceNames.hs7
-rw-r--r--XMonad/Hooks/ManageHelpers.hs3
-rw-r--r--XMonad/Hooks/UrgencyHook.hs3
-rw-r--r--XMonad/Layout/AutoMaster.hs2
-rw-r--r--XMonad/Layout/BorderResize.hs1
-rw-r--r--XMonad/Layout/ButtonDecoration.hs3
-rw-r--r--XMonad/Layout/CenteredMaster.hs3
-rw-r--r--XMonad/Layout/Decoration.hs1
-rw-r--r--XMonad/Layout/DraggingVisualizer.hs3
-rw-r--r--XMonad/Layout/Drawer.hs2
-rw-r--r--XMonad/Layout/Gaps.hs2
-rw-r--r--XMonad/Layout/Groups.hs2
-rw-r--r--XMonad/Layout/IM.hs1
-rw-r--r--XMonad/Layout/ImageButtonDecoration.hs1
-rw-r--r--XMonad/Layout/LayoutBuilder.hs3
-rw-r--r--XMonad/Layout/LayoutCombinators.hs3
-rw-r--r--XMonad/Layout/LayoutHints.hs1
-rw-r--r--XMonad/Layout/LayoutScreens.hs3
-rw-r--r--XMonad/Layout/LimitWindows.hs3
-rw-r--r--XMonad/Layout/MagicFocus.hs3
-rw-r--r--XMonad/Layout/Magnifier.hs3
-rw-r--r--XMonad/Layout/Master.hs3
-rw-r--r--XMonad/Layout/Maximize.hs3
-rw-r--r--XMonad/Layout/Minimize.hs3
-rw-r--r--XMonad/Layout/Mosaic.hs2
-rw-r--r--XMonad/Layout/MosaicAlt.hs3
-rw-r--r--XMonad/Layout/MouseResizableTile.hs1
-rw-r--r--XMonad/Layout/MultiColumns.hs3
-rw-r--r--XMonad/Layout/MultiToggle.hs6
-rw-r--r--XMonad/Layout/NoBorders.hs3
-rw-r--r--XMonad/Layout/NoFrillsDecoration.hs1
-rw-r--r--XMonad/Layout/PositionStoreFloat.hs2
-rw-r--r--XMonad/Layout/ResizeScreen.hs1
-rw-r--r--XMonad/Layout/ShowWName.hs1
-rw-r--r--XMonad/Layout/Spacing.hs2
-rw-r--r--XMonad/Layout/Spiral.hs2
-rw-r--r--XMonad/Layout/SubLayouts.hs2
-rw-r--r--XMonad/Layout/Tabbed.hs1
-rw-r--r--XMonad/Layout/ToggleLayouts.hs2
-rw-r--r--XMonad/Layout/WindowNavigation.hs3
-rw-r--r--XMonad/Layout/WindowSwitcherDecoration.hs3
-rw-r--r--XMonad/Layout/WorkspaceDir.hs3
-rw-r--r--XMonad/Prompt.hs2
-rw-r--r--XMonad/Prompt/AppLauncher.hs3
-rw-r--r--XMonad/Prompt/AppendFile.hs3
-rw-r--r--XMonad/Prompt/DirExec.hs1
-rw-r--r--XMonad/Prompt/Directory.hs3
-rw-r--r--XMonad/Prompt/Input.hs3
-rw-r--r--XMonad/Prompt/Layout.hs6
-rw-r--r--XMonad/Prompt/Man.hs2
-rw-r--r--XMonad/Prompt/RunOrRaise.hs3
-rw-r--r--XMonad/Prompt/Ssh.hs3
-rw-r--r--XMonad/Prompt/Theme.hs1
-rw-r--r--XMonad/Prompt/Window.hs3
-rw-r--r--XMonad/Prompt/Workspace.hs5
-rw-r--r--XMonad/Prompt/XMonad.hs3
-rw-r--r--XMonad/Util/Dzen.hs4
-rw-r--r--XMonad/Util/PositionStore.hs3
65 files changed, 125 insertions, 58 deletions
diff --git a/XMonad/Actions/DynamicWorkspaceGroups.hs b/XMonad/Actions/DynamicWorkspaceGroups.hs
index 46b8e1f..4bd0679 100644
--- a/XMonad/Actions/DynamicWorkspaceGroups.hs
+++ b/XMonad/Actions/DynamicWorkspaceGroups.hs
@@ -31,6 +31,8 @@ module XMonad.Actions.DynamicWorkspaceGroups
, promptWSGroupView
, promptWSGroupAdd
, promptWSGroupForget
+
+ , WSGPrompt
) where
import Data.List (find)
@@ -134,4 +136,4 @@ promptWSGroupAdd xp s =
promptWSGroupForget :: XPConfig -> String -> X ()
promptWSGroupForget xp s = do
gs <- fmap (M.keys . unWSG) XS.get
- mkXPrompt (WSGPrompt s) xp (mkComplFunFromList' gs) forgetWSGroup \ No newline at end of file
+ mkXPrompt (WSGPrompt s) xp (mkComplFunFromList' gs) forgetWSGroup
diff --git a/XMonad/Actions/DynamicWorkspaces.hs b/XMonad/Actions/DynamicWorkspaces.hs
index 4b8156b..893dbf7 100644
--- a/XMonad/Actions/DynamicWorkspaces.hs
+++ b/XMonad/Actions/DynamicWorkspaces.hs
@@ -28,8 +28,8 @@ module XMonad.Actions.DynamicWorkspaces (
import XMonad hiding (workspaces)
import XMonad.StackSet hiding (filter, modify, delete)
-import XMonad.Prompt.Workspace
-import XMonad.Prompt ( XPConfig, mkXPrompt, XPrompt(..) )
+import XMonad.Prompt.Workspace ( Wor(Wor), workspacePrompt )
+import XMonad.Prompt ( XPConfig, mkXPrompt )
import XMonad.Util.WorkspaceCompare ( getSortByIndex )
import Data.List (find)
import Data.Maybe (isNothing)
@@ -61,11 +61,6 @@ import Control.Monad (when)
-- "XMonad.Actions.CopyWindow", 'windows', 'shift', and 'defaultXPConfig'.
-data Wor = Wor String
-
-instance XPrompt Wor where
- showXPrompt (Wor x) = x
-
mkCompl :: [String] -> String -> IO [String]
mkCompl l s = return $ filter (\x -> take (length s) x == s) l
diff --git a/XMonad/Actions/FloatKeys.hs b/XMonad/Actions/FloatKeys.hs
index 12cbb41..cad70a0 100644
--- a/XMonad/Actions/FloatKeys.hs
+++ b/XMonad/Actions/FloatKeys.hs
@@ -17,7 +17,9 @@ module XMonad.Actions.FloatKeys (
keysMoveWindow,
keysMoveWindowTo,
keysResizeWindow,
- keysAbsResizeWindow) where
+ keysAbsResizeWindow,
+ P, G,
+ ) where
import XMonad
diff --git a/XMonad/Actions/Search.hs b/XMonad/Actions/Search.hs
index 535edf3..cb15898 100644
--- a/XMonad/Actions/Search.hs
+++ b/XMonad/Actions/Search.hs
@@ -51,9 +51,12 @@ module XMonad.Actions.Search ( -- * Usage
wikipedia,
wiktionary,
youtube,
- multi
+ multi,
-- * Use case: searching with a submap
-- $tip
+
+ -- * Types
+ Browser, Site, Query, Name, Search
) where
import Codec.Binary.UTF8.String (encode)
diff --git a/XMonad/Actions/TagWindows.hs b/XMonad/Actions/TagWindows.hs
index a300f88..10331fe 100644
--- a/XMonad/Actions/TagWindows.hs
+++ b/XMonad/Actions/TagWindows.hs
@@ -22,7 +22,8 @@ module XMonad.Actions.TagWindows (
focusDownTagged, focusDownTaggedGlobal,
shiftHere, shiftToScreen,
tagPrompt,
- tagDelPrompt
+ tagDelPrompt,
+ TagPrompt,
) where
import Prelude hiding (catch)
diff --git a/XMonad/Actions/WindowNavigation.hs b/XMonad/Actions/WindowNavigation.hs
index c8b4deb..c607dd2 100644
--- a/XMonad/Actions/WindowNavigation.hs
+++ b/XMonad/Actions/WindowNavigation.hs
@@ -36,7 +36,7 @@ module XMonad.Actions.WindowNavigation (
withWindowNavigationKeys,
WNAction(..),
go, swap,
- Direction2D(..)
+ Direction2D(..), WNState,
) where
import XMonad
diff --git a/XMonad/Actions/WorkspaceCursors.hs b/XMonad/Actions/WorkspaceCursors.hs
index 0e229b0..c33d998 100644
--- a/XMonad/Actions/WorkspaceCursors.hs
+++ b/XMonad/Actions/WorkspaceCursors.hs
@@ -32,10 +32,13 @@ module XMonad.Actions.WorkspaceCursors
-- * Functions to pass to 'modifyLayer'
,focusNth'
- ,noWrapUp,noWrapDown
+ ,noWrapUp,noWrapDown,
-- * Todo
-- $todo
+
+ -- * Types
+ Cursors,
) where
import qualified XMonad.StackSet as W
diff --git a/XMonad/Actions/WorkspaceNames.hs b/XMonad/Actions/WorkspaceNames.hs
index c2dadd5..30d3d01 100644
--- a/XMonad/Actions/WorkspaceNames.hs
+++ b/XMonad/Actions/WorkspaceNames.hs
@@ -41,7 +41,8 @@ import qualified XMonad.Util.ExtensibleState as XS
import XMonad.Actions.CycleWS (findWorkspace, WSType(..), Direction1D(..))
import qualified XMonad.Actions.SwapWorkspaces as Swap
import XMonad.Hooks.DynamicLog (PP(..))
-import XMonad.Prompt (showXPrompt, mkXPrompt, XPrompt, XPConfig)
+import XMonad.Prompt (mkXPrompt, XPConfig)
+import XMonad.Prompt.Workspace (Wor(Wor))
import XMonad.Util.WorkspaceCompare (getSortByIndex)
import qualified Data.Map as M
@@ -106,10 +107,6 @@ setCurrentWorkspaceName name = do
current <- gets (W.currentTag . windowset)
setWorkspaceName current name
-data Wor = Wor String
-instance XPrompt Wor where
- showXPrompt (Wor x) = x
-
-- | Prompt for a new name for the current workspace and set it.
renameWorkspace :: XPConfig -> X ()
renameWorkspace conf = do
diff --git a/XMonad/Hooks/ManageHelpers.hs b/XMonad/Hooks/ManageHelpers.hs
index c241950..093e0cb 100644
--- a/XMonad/Hooks/ManageHelpers.hs
+++ b/XMonad/Hooks/ManageHelpers.hs
@@ -45,7 +45,8 @@ module XMonad.Hooks.ManageHelpers (
doSideFloat,
doFloatAt,
doFloatDep,
- doHideIgnore
+ doHideIgnore,
+ Match,
) where
import XMonad
diff --git a/XMonad/Hooks/UrgencyHook.hs b/XMonad/Hooks/UrgencyHook.hs
index eb9173c..6515943 100644
--- a/XMonad/Hooks/UrgencyHook.hs
+++ b/XMonad/Hooks/UrgencyHook.hs
@@ -65,7 +65,8 @@ module XMonad.Hooks.UrgencyHook (
readUrgents, withUrgents,
StdoutUrgencyHook(..),
SpawnUrgencyHook(..),
- UrgencyHook(urgencyHook)
+ UrgencyHook(urgencyHook),
+ Interval,
) where
import XMonad
diff --git a/XMonad/Layout/AutoMaster.hs b/XMonad/Layout/AutoMaster.hs
index c393bd0..370f7a9 100644
--- a/XMonad/Layout/AutoMaster.hs
+++ b/XMonad/Layout/AutoMaster.hs
@@ -18,7 +18,7 @@
module XMonad.Layout.AutoMaster (
-- * Usage
-- $usage
- autoMaster
+ autoMaster, AutoMaster
) where
import Control.Monad
diff --git a/XMonad/Layout/BorderResize.hs b/XMonad/Layout/BorderResize.hs
index ea7337a..6cc020a 100644
--- a/XMonad/Layout/BorderResize.hs
+++ b/XMonad/Layout/BorderResize.hs
@@ -24,6 +24,7 @@ module XMonad.Layout.BorderResize
-- $usage
borderResize
, BorderResize (..)
+ , RectWithBorders, BorderInfo,
) where
import XMonad
diff --git a/XMonad/Layout/ButtonDecoration.hs b/XMonad/Layout/ButtonDecoration.hs
index 43f3045..8385c07 100644
--- a/XMonad/Layout/ButtonDecoration.hs
+++ b/XMonad/Layout/ButtonDecoration.hs
@@ -22,7 +22,8 @@
module XMonad.Layout.ButtonDecoration
( -- * Usage:
-- $usage
- buttonDeco
+ buttonDeco,
+ ButtonDecoration,
) where
import XMonad
diff --git a/XMonad/Layout/CenteredMaster.hs b/XMonad/Layout/CenteredMaster.hs
index e7aab04..d7dacbe 100644
--- a/XMonad/Layout/CenteredMaster.hs
+++ b/XMonad/Layout/CenteredMaster.hs
@@ -21,7 +21,8 @@ module XMonad.Layout.CenteredMaster (
-- $usage
centerMaster,
- topRightMaster
+ topRightMaster,
+ CenteredMaster, TopRightMaster,
) where
import XMonad
diff --git a/XMonad/Layout/Decoration.hs b/XMonad/Layout/Decoration.hs
index 937b1b1..ec09575 100644
--- a/XMonad/Layout/Decoration.hs
+++ b/XMonad/Layout/Decoration.hs
@@ -27,6 +27,7 @@ module XMonad.Layout.Decoration
, isInStack, isVisible, isInvisible, isWithin, fi
, findWindowByDecoration
, module XMonad.Layout.LayoutModifier
+ , DecorationState, OrigWin
) where
import Control.Monad (when)
diff --git a/XMonad/Layout/DraggingVisualizer.hs b/XMonad/Layout/DraggingVisualizer.hs
index 157fef1..63fbeff 100644
--- a/XMonad/Layout/DraggingVisualizer.hs
+++ b/XMonad/Layout/DraggingVisualizer.hs
@@ -17,7 +17,8 @@
module XMonad.Layout.DraggingVisualizer
( draggingVisualizer,
- DraggingVisualizerMsg (..)
+ DraggingVisualizerMsg (..),
+ DraggingVisualizer,
) where
import XMonad
diff --git a/XMonad/Layout/Drawer.hs b/XMonad/Layout/Drawer.hs
index 909ecfb..9ced1a2 100644
--- a/XMonad/Layout/Drawer.hs
+++ b/XMonad/Layout/Drawer.hs
@@ -29,6 +29,8 @@ module XMonad.Layout.Drawer
, onLeft, onTop, onRight, onBottom
, module XMonad.Util.WindowProperties
+
+ , Drawer, Reflected
) where
import XMonad
diff --git a/XMonad/Layout/Gaps.hs b/XMonad/Layout/Gaps.hs
index 624206d..d4edd10 100644
--- a/XMonad/Layout/Gaps.hs
+++ b/XMonad/Layout/Gaps.hs
@@ -28,7 +28,7 @@
module XMonad.Layout.Gaps (
-- * Usage
-- $usage
- Direction2D(..),
+ Direction2D(..), Gaps,
GapSpec, gaps, GapMessage(..)
) where
diff --git a/XMonad/Layout/Groups.hs b/XMonad/Layout/Groups.hs
index 4545866..e1236ab 100644
--- a/XMonad/Layout/Groups.hs
+++ b/XMonad/Layout/Groups.hs
@@ -507,4 +507,4 @@ splitGroup l0 z@(Just s) | G l (Just ws) <- W.focus s
W.Stack f up (d:down) -> let g1 = G l $ Just $ W.Stack f up []
g2 = G l0 $ Just $ W.Stack d [] down
in insertUpZ g1 $ onFocusedZ (const g2) z
-splitGroup _ _ = Nothing \ No newline at end of file
+splitGroup _ _ = Nothing
diff --git a/XMonad/Layout/IM.hs b/XMonad/Layout/IM.hs
index d21baa2..e45fe2a 100644
--- a/XMonad/Layout/IM.hs
+++ b/XMonad/Layout/IM.hs
@@ -25,6 +25,7 @@ module XMonad.Layout.IM (
-- * TODO
-- $todo
Property(..), IM(..), withIM, gridIM,
+ AddRoster,
) where
import XMonad
diff --git a/XMonad/Layout/ImageButtonDecoration.hs b/XMonad/Layout/ImageButtonDecoration.hs
index 23c6cc3..cab72fd 100644
--- a/XMonad/Layout/ImageButtonDecoration.hs
+++ b/XMonad/Layout/ImageButtonDecoration.hs
@@ -29,6 +29,7 @@ module XMonad.Layout.ImageButtonDecoration
imageButtonDeco
, defaultThemeWithImageButtons
, imageTitleBarButtonHandler
+ , ImageButtonDecoration
) where
import XMonad
diff --git a/XMonad/Layout/LayoutBuilder.hs b/XMonad/Layout/LayoutBuilder.hs
index 434dc0a..7ac2b80 100644
--- a/XMonad/Layout/LayoutBuilder.hs
+++ b/XMonad/Layout/LayoutBuilder.hs
@@ -24,7 +24,8 @@ module XMonad.Layout.LayoutBuilder (
SubMeasure (..),
SubBox (..),
absBox,
- relBox
+ relBox,
+ LayoutN,
) where
import XMonad
diff --git a/XMonad/Layout/LayoutCombinators.hs b/XMonad/Layout/LayoutCombinators.hs
index 6d443cd..c8f19df 100644
--- a/XMonad/Layout/LayoutCombinators.hs
+++ b/XMonad/Layout/LayoutCombinators.hs
@@ -47,6 +47,9 @@ module XMonad.Layout.LayoutCombinators
-- $jtl
, (|||)
, JumpToLayout(..)
+
+ -- * Types
+ , NewSelect
) where
import Data.Maybe ( isJust, isNothing )
diff --git a/XMonad/Layout/LayoutHints.hs b/XMonad/Layout/LayoutHints.hs
index cf15295..c93b054 100644
--- a/XMonad/Layout/LayoutHints.hs
+++ b/XMonad/Layout/LayoutHints.hs
@@ -20,6 +20,7 @@ module XMonad.Layout.LayoutHints
, layoutHintsWithPlacement
, layoutHintsToCenter
, LayoutHints
+ , LayoutHintsToCenter
, hintsEventHook
) where
diff --git a/XMonad/Layout/LayoutScreens.hs b/XMonad/Layout/LayoutScreens.hs
index 25d44c9..c27a3e8 100644
--- a/XMonad/Layout/LayoutScreens.hs
+++ b/XMonad/Layout/LayoutScreens.hs
@@ -16,7 +16,8 @@
module XMonad.Layout.LayoutScreens (
-- * Usage
-- $usage
- layoutScreens, layoutSplitScreen, fixedLayout
+ layoutScreens, layoutSplitScreen, fixedLayout,
+ FixedLayout,
) where
import XMonad
diff --git a/XMonad/Layout/LimitWindows.hs b/XMonad/Layout/LimitWindows.hs
index d437b72..025a021 100644
--- a/XMonad/Layout/LimitWindows.hs
+++ b/XMonad/Layout/LimitWindows.hs
@@ -29,6 +29,9 @@ module XMonad.Layout.LimitWindows (
-- * For tests
select,update,Selection(..),updateAndSelect,
#endif
+
+ -- * Types
+ LimitWindows, Selection,
) where
import XMonad.Layout.LayoutModifier
diff --git a/XMonad/Layout/MagicFocus.hs b/XMonad/Layout/MagicFocus.hs
index bf3b31a..5e45d71 100644
--- a/XMonad/Layout/MagicFocus.hs
+++ b/XMonad/Layout/MagicFocus.hs
@@ -20,7 +20,8 @@ module XMonad.Layout.MagicFocus
promoteWarp,
promoteWarp',
followOnlyIf,
- disableFollowOnWS
+ disableFollowOnWS,
+ MagicFocus,
) where
import XMonad
diff --git a/XMonad/Layout/Magnifier.hs b/XMonad/Layout/Magnifier.hs
index 6113412..685830e 100644
--- a/XMonad/Layout/Magnifier.hs
+++ b/XMonad/Layout/Magnifier.hs
@@ -26,7 +26,8 @@ module XMonad.Layout.Magnifier
magnifiercz,
magnifiercz',
maximizeVertical,
- MagnifyMsg (..)
+ MagnifyMsg (..),
+ Magnifier,
) where
import XMonad
diff --git a/XMonad/Layout/Master.hs b/XMonad/Layout/Master.hs
index 5747f93..9f756d0 100644
--- a/XMonad/Layout/Master.hs
+++ b/XMonad/Layout/Master.hs
@@ -18,7 +18,8 @@ module XMonad.Layout.Master (
-- $usage
mastered,
- multimastered
+ multimastered,
+ AddMaster,
) where
import XMonad
diff --git a/XMonad/Layout/Maximize.hs b/XMonad/Layout/Maximize.hs
index 157a45a..f56bf07 100644
--- a/XMonad/Layout/Maximize.hs
+++ b/XMonad/Layout/Maximize.hs
@@ -19,7 +19,8 @@ module XMonad.Layout.Maximize (
-- * Usage
-- $usage
maximize,
- maximizeRestore
+ maximizeRestore,
+ Maximize, MaximizeRestore,
) where
import XMonad
diff --git a/XMonad/Layout/Minimize.hs b/XMonad/Layout/Minimize.hs
index e206ac5..89f3d24 100644
--- a/XMonad/Layout/Minimize.hs
+++ b/XMonad/Layout/Minimize.hs
@@ -19,7 +19,8 @@ module XMonad.Layout.Minimize (
-- $usage
minimize,
minimizeWindow,
- MinimizeMsg(RestoreMinimizedWin,RestoreNextMinimizedWin)
+ MinimizeMsg(RestoreMinimizedWin,RestoreNextMinimizedWin),
+ Minimize,
) where
import XMonad
diff --git a/XMonad/Layout/Mosaic.hs b/XMonad/Layout/Mosaic.hs
index 557c0ac..f993c7d 100644
--- a/XMonad/Layout/Mosaic.hs
+++ b/XMonad/Layout/Mosaic.hs
@@ -21,6 +21,8 @@ module XMonad.Layout.Mosaic (
,mosaic
,changeMaster
,changeFocused
+
+ ,Mosaic
)
where
diff --git a/XMonad/Layout/MosaicAlt.hs b/XMonad/Layout/MosaicAlt.hs
index 808053f..5f9753e 100644
--- a/XMonad/Layout/MosaicAlt.hs
+++ b/XMonad/Layout/MosaicAlt.hs
@@ -25,6 +25,9 @@ module XMonad.Layout.MosaicAlt (
, tallWindowAlt
, wideWindowAlt
, resetAlt
+
+ , Params, Param
+ , HandleWindowAlt
) where
import XMonad
diff --git a/XMonad/Layout/MouseResizableTile.hs b/XMonad/Layout/MouseResizableTile.hs
index a9bc36b..15286d6 100644
--- a/XMonad/Layout/MouseResizableTile.hs
+++ b/XMonad/Layout/MouseResizableTile.hs
@@ -30,6 +30,7 @@ module XMonad.Layout.MouseResizableTile (
isMirrored,
draggerType,
DraggerType (..),
+ MouseResizableTile,
) where
import XMonad hiding (tile, splitVertically, splitHorizontallyBy)
diff --git a/XMonad/Layout/MultiColumns.hs b/XMonad/Layout/MultiColumns.hs
index 201ba7e..c68f57b 100644
--- a/XMonad/Layout/MultiColumns.hs
+++ b/XMonad/Layout/MultiColumns.hs
@@ -18,7 +18,8 @@ module XMonad.Layout.MultiColumns (
-- * Usage
-- $usage
- multiCol
+ multiCol,
+ MultiCol,
) where
import XMonad
diff --git a/XMonad/Layout/MultiToggle.hs b/XMonad/Layout/MultiToggle.hs
index 46716a4..53b6de2 100644
--- a/XMonad/Layout/MultiToggle.hs
+++ b/XMonad/Layout/MultiToggle.hs
@@ -24,7 +24,11 @@ module XMonad.Layout.MultiToggle (
EOT(..),
single,
mkToggle,
- mkToggle1
+ mkToggle1,
+
+ HList,
+ HCons,
+ MultiToggle,
) where
import XMonad
diff --git a/XMonad/Layout/NoBorders.hs b/XMonad/Layout/NoBorders.hs
index a174183..71b72fe 100644
--- a/XMonad/Layout/NoBorders.hs
+++ b/XMonad/Layout/NoBorders.hs
@@ -27,7 +27,8 @@ module XMonad.Layout.NoBorders (
lessBorders,
SetsAmbiguous(..),
Ambiguity(..),
- With(..)
+ With(..),
+ SmartBorder, WithBorder, ConfigurableBorder,
) where
import XMonad
diff --git a/XMonad/Layout/NoFrillsDecoration.hs b/XMonad/Layout/NoFrillsDecoration.hs
index 017a9c1..c6cf122 100644
--- a/XMonad/Layout/NoFrillsDecoration.hs
+++ b/XMonad/Layout/NoFrillsDecoration.hs
@@ -22,6 +22,7 @@ module XMonad.Layout.NoFrillsDecoration
noFrillsDeco
, module XMonad.Layout.SimpleDecoration
+ , NoFrillsDecoration
) where
import XMonad.Layout.Decoration
diff --git a/XMonad/Layout/PositionStoreFloat.hs b/XMonad/Layout/PositionStoreFloat.hs
index 4797932..ea38a00 100644
--- a/XMonad/Layout/PositionStoreFloat.hs
+++ b/XMonad/Layout/PositionStoreFloat.hs
@@ -22,7 +22,7 @@
module XMonad.Layout.PositionStoreFloat
( -- * Usage
-- $usage
- positionStoreFloat
+ positionStoreFloat, PositionStoreFloat
) where
import XMonad
diff --git a/XMonad/Layout/ResizeScreen.hs b/XMonad/Layout/ResizeScreen.hs
index bcbab19..b99a35f 100644
--- a/XMonad/Layout/ResizeScreen.hs
+++ b/XMonad/Layout/ResizeScreen.hs
@@ -22,6 +22,7 @@ module XMonad.Layout.ResizeScreen
, resizeHorizontalRight, resizeVerticalBottom
, withNewRectangle
, ResizeScreen (..)
+ , ResizeMode
) where
import XMonad
diff --git a/XMonad/Layout/ShowWName.hs b/XMonad/Layout/ShowWName.hs
index 5f9d49a..d2f9096 100644
--- a/XMonad/Layout/ShowWName.hs
+++ b/XMonad/Layout/ShowWName.hs
@@ -19,6 +19,7 @@ module XMonad.Layout.ShowWName
, showWName'
, defaultSWNConfig
, SWNConfig(..)
+ , ShowWName
) where
import XMonad
diff --git a/XMonad/Layout/Spacing.hs b/XMonad/Layout/Spacing.hs
index 74f7f9c..6a2ba2c 100644
--- a/XMonad/Layout/Spacing.hs
+++ b/XMonad/Layout/Spacing.hs
@@ -17,7 +17,7 @@ module XMonad.Layout.Spacing (
-- * Usage
-- $usage
- spacing
+ spacing, Spacing,
) where
diff --git a/XMonad/Layout/Spiral.hs b/XMonad/Layout/Spiral.hs
index 6dab65f..a485d95 100644
--- a/XMonad/Layout/Spiral.hs
+++ b/XMonad/Layout/Spiral.hs
@@ -21,6 +21,8 @@ module XMonad.Layout.Spiral (
, spiralWithDir
, Rotation (..)
, Direction (..)
+
+ , SpiralWithDir
) where
import Data.Ratio
diff --git a/XMonad/Layout/SubLayouts.hs b/XMonad/Layout/SubLayouts.hs
index 20aadee..302a85a 100644
--- a/XMonad/Layout/SubLayouts.hs
+++ b/XMonad/Layout/SubLayouts.hs
@@ -28,6 +28,8 @@ module XMonad.Layout.SubLayouts (
defaultSublMap,
+ Sublayout,
+
-- * Screenshots
-- $screenshots
diff --git a/XMonad/Layout/Tabbed.hs b/XMonad/Layout/Tabbed.hs
index 9a486b1..e8455ed 100644
--- a/XMonad/Layout/Tabbed.hs
+++ b/XMonad/Layout/Tabbed.hs
@@ -26,6 +26,7 @@ module XMonad.Layout.Tabbed
, TabbedDecoration (..)
, shrinkText, CustomShrink(CustomShrink)
, Shrinker(..)
+ , TabbarShown, TabbarLocation
) where
import Data.List
diff --git a/XMonad/Layout/ToggleLayouts.hs b/XMonad/Layout/ToggleLayouts.hs
index 4ae6e66..a0193ff 100644
--- a/XMonad/Layout/ToggleLayouts.hs
+++ b/XMonad/Layout/ToggleLayouts.hs
@@ -16,7 +16,7 @@
module XMonad.Layout.ToggleLayouts (
-- * Usage
-- $usage
- toggleLayouts, ToggleLayout(..)
+ toggleLayouts, ToggleLayout(..), ToggleLayouts
) where
import XMonad
diff --git a/XMonad/Layout/WindowNavigation.hs b/XMonad/Layout/WindowNavigation.hs
index b19f25c..5587b73 100644
--- a/XMonad/Layout/WindowNavigation.hs
+++ b/XMonad/Layout/WindowNavigation.hs
@@ -21,7 +21,8 @@ module XMonad.Layout.WindowNavigation (
Navigate(..), Direction2D(..),
MoveWindowToWindow(..),
navigateColor, navigateBrightness,
- noNavigateBorders, defaultWNConfig
+ noNavigateBorders, defaultWNConfig,
+ WNConfig, WindowNavigation,
) where
import Data.List ( nub, sortBy, (\\) )
diff --git a/XMonad/Layout/WindowSwitcherDecoration.hs b/XMonad/Layout/WindowSwitcherDecoration.hs
index 34f1ab4..4778314 100644
--- a/XMonad/Layout/WindowSwitcherDecoration.hs
+++ b/XMonad/Layout/WindowSwitcherDecoration.hs
@@ -20,7 +20,8 @@ module XMonad.Layout.WindowSwitcherDecoration
-- $usage
windowSwitcherDecoration,
windowSwitcherDecorationWithButtons,
- windowSwitcherDecorationWithImageButtons
+ windowSwitcherDecorationWithImageButtons,
+ WindowSwitcherDecoration, ImageWindowSwitcherDecoration,
) where
import XMonad
diff --git a/XMonad/Layout/WorkspaceDir.hs b/XMonad/Layout/WorkspaceDir.hs
index ffffded..fda0d0e 100644
--- a/XMonad/Layout/WorkspaceDir.hs
+++ b/XMonad/Layout/WorkspaceDir.hs
@@ -25,7 +25,8 @@ module XMonad.Layout.WorkspaceDir (
-- * Usage
-- $usage
workspaceDir,
- changeDir
+ changeDir,
+ WorkspaceDir,
) where
import Prelude hiding (catch)
diff --git a/XMonad/Prompt.hs b/XMonad/Prompt.hs
index 1d2faba..d835b78 100644
--- a/XMonad/Prompt.hs
+++ b/XMonad/Prompt.hs
@@ -61,6 +61,8 @@ module XMonad.Prompt
, initMatches
, historyUpMatching
, historyDownMatching
+ -- * Types
+ , XPState
) where
import Prelude hiding (catch)
diff --git a/XMonad/Prompt/AppLauncher.hs b/XMonad/Prompt/AppLauncher.hs
index 7af348b..167c798 100644
--- a/XMonad/Prompt/AppLauncher.hs
+++ b/XMonad/Prompt/AppLauncher.hs
@@ -18,6 +18,9 @@ module XMonad.Prompt.AppLauncher ( -- * Usage
,module XMonad.Prompt
-- * Use case: launching gimp with file
-- $tip
+
+ -- * Types
+ ,Application, AppPrompt,
) where
import XMonad (X(),MonadIO)
diff --git a/XMonad/Prompt/AppendFile.hs b/XMonad/Prompt/AppendFile.hs
index 945c8de..17d4763 100644
--- a/XMonad/Prompt/AppendFile.hs
+++ b/XMonad/Prompt/AppendFile.hs
@@ -22,7 +22,8 @@ module XMonad.Prompt.AppendFile (
-- * Usage
-- $usage
- appendFilePrompt
+ appendFilePrompt,
+ AppendFile,
) where
import XMonad.Core
diff --git a/XMonad/Prompt/DirExec.hs b/XMonad/Prompt/DirExec.hs
index 1600f93..ddcc8c5 100644
--- a/XMonad/Prompt/DirExec.hs
+++ b/XMonad/Prompt/DirExec.hs
@@ -21,6 +21,7 @@ module XMonad.Prompt.DirExec
-- $usage
dirExecPrompt
, dirExecPromptNamed
+ , DirExec
) where
import Prelude hiding (catch)
diff --git a/XMonad/Prompt/Directory.hs b/XMonad/Prompt/Directory.hs
index a2791bb..63599af 100644
--- a/XMonad/Prompt/Directory.hs
+++ b/XMonad/Prompt/Directory.hs
@@ -15,7 +15,8 @@
module XMonad.Prompt.Directory (
-- * Usage
-- $usage
- directoryPrompt
+ directoryPrompt,
+ Dir,
) where
import XMonad
diff --git a/XMonad/Prompt/Input.hs b/XMonad/Prompt/Input.hs
index 124fe92..8342856 100644
--- a/XMonad/Prompt/Input.hs
+++ b/XMonad/Prompt/Input.hs
@@ -18,7 +18,8 @@ module XMonad.Prompt.Input (
-- $usage
inputPrompt,
inputPromptWithCompl,
- (?+)
+ (?+),
+ InputPrompt,
) where
import XMonad.Core
diff --git a/XMonad/Prompt/Layout.hs b/XMonad/Prompt/Layout.hs
index a824e73..d9c59e1 100644
--- a/XMonad/Prompt/Layout.hs
+++ b/XMonad/Prompt/Layout.hs
@@ -21,6 +21,7 @@ module XMonad.Prompt.Layout (
import Data.List ( sort, nub )
import XMonad hiding ( workspaces )
import XMonad.Prompt
+import XMonad.Prompt.Workspace ( Wor(..) )
import XMonad.StackSet ( workspaces, layout )
import XMonad.Layout.LayoutCombinators ( JumpToLayout(..) )
@@ -43,11 +44,6 @@ import XMonad.Layout.LayoutCombinators ( JumpToLayout(..) )
-- more a proof-of-principle than something you can actually use
-- productively.
-data Wor = Wor String
-
-instance XPrompt Wor where
- showXPrompt (Wor x) = x
-
layoutPrompt :: XPConfig -> X ()
layoutPrompt c = do ls <- gets (map (description . layout) . workspaces . windowset)
mkXPrompt (Wor "") c (mkComplFunFromList' $ sort $ nub ls) (sendMessage . JumpToLayout)
diff --git a/XMonad/Prompt/Man.hs b/XMonad/Prompt/Man.hs
index aae6a33..c5bd8d5 100644
--- a/XMonad/Prompt/Man.hs
+++ b/XMonad/Prompt/Man.hs
@@ -20,8 +20,10 @@ module XMonad.Prompt.Man (
-- $usage
manPrompt
, getCommandOutput
+ , Man
) where
+
import XMonad
import XMonad.Prompt
import XMonad.Util.Run
diff --git a/XMonad/Prompt/RunOrRaise.hs b/XMonad/Prompt/RunOrRaise.hs
index 251e09c..8fb5c43 100644
--- a/XMonad/Prompt/RunOrRaise.hs
+++ b/XMonad/Prompt/RunOrRaise.hs
@@ -16,7 +16,8 @@
module XMonad.Prompt.RunOrRaise
( -- * Usage
-- $usage
- runOrRaisePrompt
+ runOrRaisePrompt,
+ RunOrRaisePrompt,
) where
import XMonad hiding (config)
diff --git a/XMonad/Prompt/Ssh.hs b/XMonad/Prompt/Ssh.hs
index 7d84069..c3a035d 100644
--- a/XMonad/Prompt/Ssh.hs
+++ b/XMonad/Prompt/Ssh.hs
@@ -15,7 +15,8 @@
module XMonad.Prompt.Ssh
( -- * Usage
-- $usage
- sshPrompt
+ sshPrompt,
+ Ssh,
) where
import Prelude hiding (catch)
diff --git a/XMonad/Prompt/Theme.hs b/XMonad/Prompt/Theme.hs
index 653b16c..d34dd87 100644
--- a/XMonad/Prompt/Theme.hs
+++ b/XMonad/Prompt/Theme.hs
@@ -15,6 +15,7 @@ module XMonad.Prompt.Theme
( -- * Usage
-- $usage
themePrompt,
+ ThemePrompt,
) where
import Control.Arrow ( (&&&) )
diff --git a/XMonad/Prompt/Window.hs b/XMonad/Prompt/Window.hs
index a5b6aeb..a6aa53f 100644
--- a/XMonad/Prompt/Window.hs
+++ b/XMonad/Prompt/Window.hs
@@ -20,7 +20,8 @@ module XMonad.Prompt.Window
-- $usage
windowPromptGoto,
windowPromptBring,
- windowPromptBringCopy
+ windowPromptBringCopy,
+ WindowPrompt,
) where
import qualified Data.Map as M
diff --git a/XMonad/Prompt/Workspace.hs b/XMonad/Prompt/Workspace.hs
index 1b49f06..749ca9d 100644
--- a/XMonad/Prompt/Workspace.hs
+++ b/XMonad/Prompt/Workspace.hs
@@ -15,7 +15,10 @@
module XMonad.Prompt.Workspace (
-- * Usage
-- $usage
- workspacePrompt
+ workspacePrompt,
+
+ -- * For developers
+ Wor(Wor),
) where
import XMonad hiding ( workspaces )
diff --git a/XMonad/Prompt/XMonad.hs b/XMonad/Prompt/XMonad.hs
index 184017f..86f5369 100644
--- a/XMonad/Prompt/XMonad.hs
+++ b/XMonad/Prompt/XMonad.hs
@@ -16,7 +16,8 @@ module XMonad.Prompt.XMonad (
-- * Usage
-- $usage
xmonadPrompt,
- xmonadPromptC
+ xmonadPromptC,
+ XMonad,
) where
import XMonad
diff --git a/XMonad/Util/Dzen.hs b/XMonad/Util/Dzen.hs
index 05ff2ea..910beca 100644
--- a/XMonad/Util/Dzen.hs
+++ b/XMonad/Util/Dzen.hs
@@ -14,7 +14,7 @@
module XMonad.Util.Dzen (
-- * Flexible interface
- dzenConfig,
+ dzenConfig, DzenConfig,
timeout,
font,
xScreen,
@@ -34,7 +34,7 @@ module XMonad.Util.Dzen (
-- * Miscellaneous
seconds,
chomp,
- (>=>)
+ (>=>),
) where
import Control.Monad
diff --git a/XMonad/Util/PositionStore.hs b/XMonad/Util/PositionStore.hs
index 52c616a..02974bf 100644
--- a/XMonad/Util/PositionStore.hs
+++ b/XMonad/Util/PositionStore.hs
@@ -22,7 +22,8 @@ module XMonad.Util.PositionStore (
posStoreInsert,
posStoreMove,
posStoreQuery,
- posStoreRemove
+ posStoreRemove,
+ PositionStore,
) where
import XMonad