Export types to reduce haddock warnings.

This commit is contained in:
Adam Vogt 2010-10-23 19:57:55 +00:00
parent 0226b8cb4f
commit 067ccb950e
65 changed files with 125 additions and 58 deletions

View File

@ -31,6 +31,8 @@ module XMonad.Actions.DynamicWorkspaceGroups
, promptWSGroupView , promptWSGroupView
, promptWSGroupAdd , promptWSGroupAdd
, promptWSGroupForget , promptWSGroupForget
, WSGPrompt
) where ) where
import Data.List (find) import Data.List (find)
@ -134,4 +136,4 @@ promptWSGroupAdd xp s =
promptWSGroupForget :: XPConfig -> String -> X () promptWSGroupForget :: XPConfig -> String -> X ()
promptWSGroupForget xp s = do promptWSGroupForget xp s = do
gs <- fmap (M.keys . unWSG) XS.get gs <- fmap (M.keys . unWSG) XS.get
mkXPrompt (WSGPrompt s) xp (mkComplFunFromList' gs) forgetWSGroup mkXPrompt (WSGPrompt s) xp (mkComplFunFromList' gs) forgetWSGroup

View File

@ -28,8 +28,8 @@ module XMonad.Actions.DynamicWorkspaces (
import XMonad hiding (workspaces) import XMonad hiding (workspaces)
import XMonad.StackSet hiding (filter, modify, delete) import XMonad.StackSet hiding (filter, modify, delete)
import XMonad.Prompt.Workspace import XMonad.Prompt.Workspace ( Wor(Wor), workspacePrompt )
import XMonad.Prompt ( XPConfig, mkXPrompt, XPrompt(..) ) import XMonad.Prompt ( XPConfig, mkXPrompt )
import XMonad.Util.WorkspaceCompare ( getSortByIndex ) import XMonad.Util.WorkspaceCompare ( getSortByIndex )
import Data.List (find) import Data.List (find)
import Data.Maybe (isNothing) import Data.Maybe (isNothing)
@ -61,11 +61,6 @@ import Control.Monad (when)
-- "XMonad.Actions.CopyWindow", 'windows', 'shift', and 'defaultXPConfig'. -- "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 :: [String] -> String -> IO [String]
mkCompl l s = return $ filter (\x -> take (length s) x == s) l mkCompl l s = return $ filter (\x -> take (length s) x == s) l

View File

@ -17,7 +17,9 @@ module XMonad.Actions.FloatKeys (
keysMoveWindow, keysMoveWindow,
keysMoveWindowTo, keysMoveWindowTo,
keysResizeWindow, keysResizeWindow,
keysAbsResizeWindow) where keysAbsResizeWindow,
P, G,
) where
import XMonad import XMonad

View File

@ -51,9 +51,12 @@ module XMonad.Actions.Search ( -- * Usage
wikipedia, wikipedia,
wiktionary, wiktionary,
youtube, youtube,
multi multi,
-- * Use case: searching with a submap -- * Use case: searching with a submap
-- $tip -- $tip
-- * Types
Browser, Site, Query, Name, Search
) where ) where
import Codec.Binary.UTF8.String (encode) import Codec.Binary.UTF8.String (encode)

View File

@ -22,7 +22,8 @@ module XMonad.Actions.TagWindows (
focusDownTagged, focusDownTaggedGlobal, focusDownTagged, focusDownTaggedGlobal,
shiftHere, shiftToScreen, shiftHere, shiftToScreen,
tagPrompt, tagPrompt,
tagDelPrompt tagDelPrompt,
TagPrompt,
) where ) where
import Prelude hiding (catch) import Prelude hiding (catch)

View File

@ -36,7 +36,7 @@ module XMonad.Actions.WindowNavigation (
withWindowNavigationKeys, withWindowNavigationKeys,
WNAction(..), WNAction(..),
go, swap, go, swap,
Direction2D(..) Direction2D(..), WNState,
) where ) where
import XMonad import XMonad

View File

@ -32,10 +32,13 @@ module XMonad.Actions.WorkspaceCursors
-- * Functions to pass to 'modifyLayer' -- * Functions to pass to 'modifyLayer'
,focusNth' ,focusNth'
,noWrapUp,noWrapDown ,noWrapUp,noWrapDown,
-- * Todo -- * Todo
-- $todo -- $todo
-- * Types
Cursors,
) where ) where
import qualified XMonad.StackSet as W import qualified XMonad.StackSet as W

View File

@ -41,7 +41,8 @@ import qualified XMonad.Util.ExtensibleState as XS
import XMonad.Actions.CycleWS (findWorkspace, WSType(..), Direction1D(..)) import XMonad.Actions.CycleWS (findWorkspace, WSType(..), Direction1D(..))
import qualified XMonad.Actions.SwapWorkspaces as Swap import qualified XMonad.Actions.SwapWorkspaces as Swap
import XMonad.Hooks.DynamicLog (PP(..)) 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 XMonad.Util.WorkspaceCompare (getSortByIndex)
import qualified Data.Map as M import qualified Data.Map as M
@ -106,10 +107,6 @@ setCurrentWorkspaceName name = do
current <- gets (W.currentTag . windowset) current <- gets (W.currentTag . windowset)
setWorkspaceName current name 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. -- | Prompt for a new name for the current workspace and set it.
renameWorkspace :: XPConfig -> X () renameWorkspace :: XPConfig -> X ()
renameWorkspace conf = do renameWorkspace conf = do

View File

@ -45,7 +45,8 @@ module XMonad.Hooks.ManageHelpers (
doSideFloat, doSideFloat,
doFloatAt, doFloatAt,
doFloatDep, doFloatDep,
doHideIgnore doHideIgnore,
Match,
) where ) where
import XMonad import XMonad

View File

@ -65,7 +65,8 @@ module XMonad.Hooks.UrgencyHook (
readUrgents, withUrgents, readUrgents, withUrgents,
StdoutUrgencyHook(..), StdoutUrgencyHook(..),
SpawnUrgencyHook(..), SpawnUrgencyHook(..),
UrgencyHook(urgencyHook) UrgencyHook(urgencyHook),
Interval,
) where ) where
import XMonad import XMonad

View File

@ -18,7 +18,7 @@
module XMonad.Layout.AutoMaster ( module XMonad.Layout.AutoMaster (
-- * Usage -- * Usage
-- $usage -- $usage
autoMaster autoMaster, AutoMaster
) where ) where
import Control.Monad import Control.Monad

View File

@ -24,6 +24,7 @@ module XMonad.Layout.BorderResize
-- $usage -- $usage
borderResize borderResize
, BorderResize (..) , BorderResize (..)
, RectWithBorders, BorderInfo,
) where ) where
import XMonad import XMonad

View File

@ -22,7 +22,8 @@
module XMonad.Layout.ButtonDecoration module XMonad.Layout.ButtonDecoration
( -- * Usage: ( -- * Usage:
-- $usage -- $usage
buttonDeco buttonDeco,
ButtonDecoration,
) where ) where
import XMonad import XMonad

View File

@ -21,7 +21,8 @@ module XMonad.Layout.CenteredMaster (
-- $usage -- $usage
centerMaster, centerMaster,
topRightMaster topRightMaster,
CenteredMaster, TopRightMaster,
) where ) where
import XMonad import XMonad

View File

@ -27,6 +27,7 @@ module XMonad.Layout.Decoration
, isInStack, isVisible, isInvisible, isWithin, fi , isInStack, isVisible, isInvisible, isWithin, fi
, findWindowByDecoration , findWindowByDecoration
, module XMonad.Layout.LayoutModifier , module XMonad.Layout.LayoutModifier
, DecorationState, OrigWin
) where ) where
import Control.Monad (when) import Control.Monad (when)

View File

@ -17,7 +17,8 @@
module XMonad.Layout.DraggingVisualizer module XMonad.Layout.DraggingVisualizer
( draggingVisualizer, ( draggingVisualizer,
DraggingVisualizerMsg (..) DraggingVisualizerMsg (..),
DraggingVisualizer,
) where ) where
import XMonad import XMonad

View File

@ -29,6 +29,8 @@ module XMonad.Layout.Drawer
, onLeft, onTop, onRight, onBottom , onLeft, onTop, onRight, onBottom
, module XMonad.Util.WindowProperties , module XMonad.Util.WindowProperties
, Drawer, Reflected
) where ) where
import XMonad import XMonad

View File

@ -28,7 +28,7 @@
module XMonad.Layout.Gaps ( module XMonad.Layout.Gaps (
-- * Usage -- * Usage
-- $usage -- $usage
Direction2D(..), Direction2D(..), Gaps,
GapSpec, gaps, GapMessage(..) GapSpec, gaps, GapMessage(..)
) where ) where

View File

@ -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 [] W.Stack f up (d:down) -> let g1 = G l $ Just $ W.Stack f up []
g2 = G l0 $ Just $ W.Stack d [] down g2 = G l0 $ Just $ W.Stack d [] down
in insertUpZ g1 $ onFocusedZ (const g2) z in insertUpZ g1 $ onFocusedZ (const g2) z
splitGroup _ _ = Nothing splitGroup _ _ = Nothing

View File

@ -25,6 +25,7 @@ module XMonad.Layout.IM (
-- * TODO -- * TODO
-- $todo -- $todo
Property(..), IM(..), withIM, gridIM, Property(..), IM(..), withIM, gridIM,
AddRoster,
) where ) where
import XMonad import XMonad

View File

@ -29,6 +29,7 @@ module XMonad.Layout.ImageButtonDecoration
imageButtonDeco imageButtonDeco
, defaultThemeWithImageButtons , defaultThemeWithImageButtons
, imageTitleBarButtonHandler , imageTitleBarButtonHandler
, ImageButtonDecoration
) where ) where
import XMonad import XMonad

View File

@ -24,7 +24,8 @@ module XMonad.Layout.LayoutBuilder (
SubMeasure (..), SubMeasure (..),
SubBox (..), SubBox (..),
absBox, absBox,
relBox relBox,
LayoutN,
) where ) where
import XMonad import XMonad

View File

@ -47,6 +47,9 @@ module XMonad.Layout.LayoutCombinators
-- $jtl -- $jtl
, (|||) , (|||)
, JumpToLayout(..) , JumpToLayout(..)
-- * Types
, NewSelect
) where ) where
import Data.Maybe ( isJust, isNothing ) import Data.Maybe ( isJust, isNothing )

View File

@ -20,6 +20,7 @@ module XMonad.Layout.LayoutHints
, layoutHintsWithPlacement , layoutHintsWithPlacement
, layoutHintsToCenter , layoutHintsToCenter
, LayoutHints , LayoutHints
, LayoutHintsToCenter
, hintsEventHook , hintsEventHook
) where ) where

View File

@ -16,7 +16,8 @@
module XMonad.Layout.LayoutScreens ( module XMonad.Layout.LayoutScreens (
-- * Usage -- * Usage
-- $usage -- $usage
layoutScreens, layoutSplitScreen, fixedLayout layoutScreens, layoutSplitScreen, fixedLayout,
FixedLayout,
) where ) where
import XMonad import XMonad

View File

@ -29,6 +29,9 @@ module XMonad.Layout.LimitWindows (
-- * For tests -- * For tests
select,update,Selection(..),updateAndSelect, select,update,Selection(..),updateAndSelect,
#endif #endif
-- * Types
LimitWindows, Selection,
) where ) where
import XMonad.Layout.LayoutModifier import XMonad.Layout.LayoutModifier

View File

@ -20,7 +20,8 @@ module XMonad.Layout.MagicFocus
promoteWarp, promoteWarp,
promoteWarp', promoteWarp',
followOnlyIf, followOnlyIf,
disableFollowOnWS disableFollowOnWS,
MagicFocus,
) where ) where
import XMonad import XMonad

View File

@ -26,7 +26,8 @@ module XMonad.Layout.Magnifier
magnifiercz, magnifiercz,
magnifiercz', magnifiercz',
maximizeVertical, maximizeVertical,
MagnifyMsg (..) MagnifyMsg (..),
Magnifier,
) where ) where
import XMonad import XMonad

View File

@ -18,7 +18,8 @@ module XMonad.Layout.Master (
-- $usage -- $usage
mastered, mastered,
multimastered multimastered,
AddMaster,
) where ) where
import XMonad import XMonad

View File

@ -19,7 +19,8 @@ module XMonad.Layout.Maximize (
-- * Usage -- * Usage
-- $usage -- $usage
maximize, maximize,
maximizeRestore maximizeRestore,
Maximize, MaximizeRestore,
) where ) where
import XMonad import XMonad

View File

@ -19,7 +19,8 @@ module XMonad.Layout.Minimize (
-- $usage -- $usage
minimize, minimize,
minimizeWindow, minimizeWindow,
MinimizeMsg(RestoreMinimizedWin,RestoreNextMinimizedWin) MinimizeMsg(RestoreMinimizedWin,RestoreNextMinimizedWin),
Minimize,
) where ) where
import XMonad import XMonad

View File

@ -21,6 +21,8 @@ module XMonad.Layout.Mosaic (
,mosaic ,mosaic
,changeMaster ,changeMaster
,changeFocused ,changeFocused
,Mosaic
) )
where where

View File

@ -25,6 +25,9 @@ module XMonad.Layout.MosaicAlt (
, tallWindowAlt , tallWindowAlt
, wideWindowAlt , wideWindowAlt
, resetAlt , resetAlt
, Params, Param
, HandleWindowAlt
) where ) where
import XMonad import XMonad

View File

@ -30,6 +30,7 @@ module XMonad.Layout.MouseResizableTile (
isMirrored, isMirrored,
draggerType, draggerType,
DraggerType (..), DraggerType (..),
MouseResizableTile,
) where ) where
import XMonad hiding (tile, splitVertically, splitHorizontallyBy) import XMonad hiding (tile, splitVertically, splitHorizontallyBy)

View File

@ -18,7 +18,8 @@ module XMonad.Layout.MultiColumns (
-- * Usage -- * Usage
-- $usage -- $usage
multiCol multiCol,
MultiCol,
) where ) where
import XMonad import XMonad

View File

@ -24,7 +24,11 @@ module XMonad.Layout.MultiToggle (
EOT(..), EOT(..),
single, single,
mkToggle, mkToggle,
mkToggle1 mkToggle1,
HList,
HCons,
MultiToggle,
) where ) where
import XMonad import XMonad

View File

@ -27,7 +27,8 @@ module XMonad.Layout.NoBorders (
lessBorders, lessBorders,
SetsAmbiguous(..), SetsAmbiguous(..),
Ambiguity(..), Ambiguity(..),
With(..) With(..),
SmartBorder, WithBorder, ConfigurableBorder,
) where ) where
import XMonad import XMonad

View File

@ -22,6 +22,7 @@ module XMonad.Layout.NoFrillsDecoration
noFrillsDeco noFrillsDeco
, module XMonad.Layout.SimpleDecoration , module XMonad.Layout.SimpleDecoration
, NoFrillsDecoration
) where ) where
import XMonad.Layout.Decoration import XMonad.Layout.Decoration

View File

@ -22,7 +22,7 @@
module XMonad.Layout.PositionStoreFloat module XMonad.Layout.PositionStoreFloat
( -- * Usage ( -- * Usage
-- $usage -- $usage
positionStoreFloat positionStoreFloat, PositionStoreFloat
) where ) where
import XMonad import XMonad

View File

@ -22,6 +22,7 @@ module XMonad.Layout.ResizeScreen
, resizeHorizontalRight, resizeVerticalBottom , resizeHorizontalRight, resizeVerticalBottom
, withNewRectangle , withNewRectangle
, ResizeScreen (..) , ResizeScreen (..)
, ResizeMode
) where ) where
import XMonad import XMonad

View File

@ -19,6 +19,7 @@ module XMonad.Layout.ShowWName
, showWName' , showWName'
, defaultSWNConfig , defaultSWNConfig
, SWNConfig(..) , SWNConfig(..)
, ShowWName
) where ) where
import XMonad import XMonad

View File

@ -17,7 +17,7 @@ module XMonad.Layout.Spacing (
-- * Usage -- * Usage
-- $usage -- $usage
spacing spacing, Spacing,
) where ) where

View File

@ -21,6 +21,8 @@ module XMonad.Layout.Spiral (
, spiralWithDir , spiralWithDir
, Rotation (..) , Rotation (..)
, Direction (..) , Direction (..)
, SpiralWithDir
) where ) where
import Data.Ratio import Data.Ratio

View File

@ -28,6 +28,8 @@ module XMonad.Layout.SubLayouts (
defaultSublMap, defaultSublMap,
Sublayout,
-- * Screenshots -- * Screenshots
-- $screenshots -- $screenshots

View File

@ -26,6 +26,7 @@ module XMonad.Layout.Tabbed
, TabbedDecoration (..) , TabbedDecoration (..)
, shrinkText, CustomShrink(CustomShrink) , shrinkText, CustomShrink(CustomShrink)
, Shrinker(..) , Shrinker(..)
, TabbarShown, TabbarLocation
) where ) where
import Data.List import Data.List

View File

@ -16,7 +16,7 @@
module XMonad.Layout.ToggleLayouts ( module XMonad.Layout.ToggleLayouts (
-- * Usage -- * Usage
-- $usage -- $usage
toggleLayouts, ToggleLayout(..) toggleLayouts, ToggleLayout(..), ToggleLayouts
) where ) where
import XMonad import XMonad

View File

@ -21,7 +21,8 @@ module XMonad.Layout.WindowNavigation (
Navigate(..), Direction2D(..), Navigate(..), Direction2D(..),
MoveWindowToWindow(..), MoveWindowToWindow(..),
navigateColor, navigateBrightness, navigateColor, navigateBrightness,
noNavigateBorders, defaultWNConfig noNavigateBorders, defaultWNConfig,
WNConfig, WindowNavigation,
) where ) where
import Data.List ( nub, sortBy, (\\) ) import Data.List ( nub, sortBy, (\\) )

View File

@ -20,7 +20,8 @@ module XMonad.Layout.WindowSwitcherDecoration
-- $usage -- $usage
windowSwitcherDecoration, windowSwitcherDecoration,
windowSwitcherDecorationWithButtons, windowSwitcherDecorationWithButtons,
windowSwitcherDecorationWithImageButtons windowSwitcherDecorationWithImageButtons,
WindowSwitcherDecoration, ImageWindowSwitcherDecoration,
) where ) where
import XMonad import XMonad

View File

@ -25,7 +25,8 @@ module XMonad.Layout.WorkspaceDir (
-- * Usage -- * Usage
-- $usage -- $usage
workspaceDir, workspaceDir,
changeDir changeDir,
WorkspaceDir,
) where ) where
import Prelude hiding (catch) import Prelude hiding (catch)

View File

@ -61,6 +61,8 @@ module XMonad.Prompt
, initMatches , initMatches
, historyUpMatching , historyUpMatching
, historyDownMatching , historyDownMatching
-- * Types
, XPState
) where ) where
import Prelude hiding (catch) import Prelude hiding (catch)

View File

@ -18,6 +18,9 @@ module XMonad.Prompt.AppLauncher ( -- * Usage
,module XMonad.Prompt ,module XMonad.Prompt
-- * Use case: launching gimp with file -- * Use case: launching gimp with file
-- $tip -- $tip
-- * Types
,Application, AppPrompt,
) where ) where
import XMonad (X(),MonadIO) import XMonad (X(),MonadIO)

View File

@ -22,7 +22,8 @@ module XMonad.Prompt.AppendFile (
-- * Usage -- * Usage
-- $usage -- $usage
appendFilePrompt appendFilePrompt,
AppendFile,
) where ) where
import XMonad.Core import XMonad.Core

View File

@ -21,6 +21,7 @@ module XMonad.Prompt.DirExec
-- $usage -- $usage
dirExecPrompt dirExecPrompt
, dirExecPromptNamed , dirExecPromptNamed
, DirExec
) where ) where
import Prelude hiding (catch) import Prelude hiding (catch)

View File

@ -15,7 +15,8 @@
module XMonad.Prompt.Directory ( module XMonad.Prompt.Directory (
-- * Usage -- * Usage
-- $usage -- $usage
directoryPrompt directoryPrompt,
Dir,
) where ) where
import XMonad import XMonad

View File

@ -18,7 +18,8 @@ module XMonad.Prompt.Input (
-- $usage -- $usage
inputPrompt, inputPrompt,
inputPromptWithCompl, inputPromptWithCompl,
(?+) (?+),
InputPrompt,
) where ) where
import XMonad.Core import XMonad.Core

View File

@ -21,6 +21,7 @@ module XMonad.Prompt.Layout (
import Data.List ( sort, nub ) import Data.List ( sort, nub )
import XMonad hiding ( workspaces ) import XMonad hiding ( workspaces )
import XMonad.Prompt import XMonad.Prompt
import XMonad.Prompt.Workspace ( Wor(..) )
import XMonad.StackSet ( workspaces, layout ) import XMonad.StackSet ( workspaces, layout )
import XMonad.Layout.LayoutCombinators ( JumpToLayout(..) ) 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 -- more a proof-of-principle than something you can actually use
-- productively. -- productively.
data Wor = Wor String
instance XPrompt Wor where
showXPrompt (Wor x) = x
layoutPrompt :: XPConfig -> X () layoutPrompt :: XPConfig -> X ()
layoutPrompt c = do ls <- gets (map (description . layout) . workspaces . windowset) layoutPrompt c = do ls <- gets (map (description . layout) . workspaces . windowset)
mkXPrompt (Wor "") c (mkComplFunFromList' $ sort $ nub ls) (sendMessage . JumpToLayout) mkXPrompt (Wor "") c (mkComplFunFromList' $ sort $ nub ls) (sendMessage . JumpToLayout)

View File

@ -20,8 +20,10 @@ module XMonad.Prompt.Man (
-- $usage -- $usage
manPrompt manPrompt
, getCommandOutput , getCommandOutput
, Man
) where ) where
import XMonad import XMonad
import XMonad.Prompt import XMonad.Prompt
import XMonad.Util.Run import XMonad.Util.Run

View File

@ -16,7 +16,8 @@
module XMonad.Prompt.RunOrRaise module XMonad.Prompt.RunOrRaise
( -- * Usage ( -- * Usage
-- $usage -- $usage
runOrRaisePrompt runOrRaisePrompt,
RunOrRaisePrompt,
) where ) where
import XMonad hiding (config) import XMonad hiding (config)

View File

@ -15,7 +15,8 @@
module XMonad.Prompt.Ssh module XMonad.Prompt.Ssh
( -- * Usage ( -- * Usage
-- $usage -- $usage
sshPrompt sshPrompt,
Ssh,
) where ) where
import Prelude hiding (catch) import Prelude hiding (catch)

View File

@ -15,6 +15,7 @@ module XMonad.Prompt.Theme
( -- * Usage ( -- * Usage
-- $usage -- $usage
themePrompt, themePrompt,
ThemePrompt,
) where ) where
import Control.Arrow ( (&&&) ) import Control.Arrow ( (&&&) )

View File

@ -20,7 +20,8 @@ module XMonad.Prompt.Window
-- $usage -- $usage
windowPromptGoto, windowPromptGoto,
windowPromptBring, windowPromptBring,
windowPromptBringCopy windowPromptBringCopy,
WindowPrompt,
) where ) where
import qualified Data.Map as M import qualified Data.Map as M

View File

@ -15,7 +15,10 @@
module XMonad.Prompt.Workspace ( module XMonad.Prompt.Workspace (
-- * Usage -- * Usage
-- $usage -- $usage
workspacePrompt workspacePrompt,
-- * For developers
Wor(Wor),
) where ) where
import XMonad hiding ( workspaces ) import XMonad hiding ( workspaces )

View File

@ -16,7 +16,8 @@ module XMonad.Prompt.XMonad (
-- * Usage -- * Usage
-- $usage -- $usage
xmonadPrompt, xmonadPrompt,
xmonadPromptC xmonadPromptC,
XMonad,
) where ) where
import XMonad import XMonad

View File

@ -14,7 +14,7 @@
module XMonad.Util.Dzen ( module XMonad.Util.Dzen (
-- * Flexible interface -- * Flexible interface
dzenConfig, dzenConfig, DzenConfig,
timeout, timeout,
font, font,
xScreen, xScreen,
@ -34,7 +34,7 @@ module XMonad.Util.Dzen (
-- * Miscellaneous -- * Miscellaneous
seconds, seconds,
chomp, chomp,
(>=>) (>=>),
) where ) where
import Control.Monad import Control.Monad

View File

@ -22,7 +22,8 @@ module XMonad.Util.PositionStore (
posStoreInsert, posStoreInsert,
posStoreMove, posStoreMove,
posStoreQuery, posStoreQuery,
posStoreRemove posStoreRemove,
PositionStore,
) where ) where
import XMonad import XMonad