-- Hoogle documentation, generated by Haddock -- See Hoogle, http://www.haskell.org/hoogle/ -- | Third party extensions for xmonad -- -- Third party tiling algorithms, configurations and scripts to xmonad, a -- tiling window manager for X. -- -- For an introduction to building, configuring and using xmonad -- extensions, see XMonad.Doc. In particular: -- -- XMonad.Doc.Configuring, a guide to configuring xmonad -- -- XMonad.Doc.Extending, using the contributed extensions library -- -- XMonad.Doc.Developing, introduction to xmonad internals and -- writing your own extensions. @package xmonad-contrib @version 0.12 -- | Functions for saving per-window data. module XMonad.Util.WindowState -- | Return the state from the internals of the monad. get :: MonadState s m => m s -- | Replace the state inside the monad. put :: MonadState s m => s -> m () -- | Wrapper around Query with phanom type s, representing -- state, saved in window. newtype StateQuery s a StateQuery :: Query a -> StateQuery s a [getQuery] :: StateQuery s a -> Query a -- | Apply StateQuery to Window. runStateQuery :: StateQuery s a -> Window -> X a -- | Lifted to Query version of catchX catchQuery :: Query a -> Query (Maybe a) instance GHC.Base.Functor (XMonad.Util.WindowState.StateQuery s) instance GHC.Base.Applicative (XMonad.Util.WindowState.StateQuery s) instance Control.Monad.IO.Class.MonadIO (XMonad.Util.WindowState.StateQuery s) instance GHC.Base.Monad (XMonad.Util.WindowState.StateQuery s) instance (GHC.Show.Show s, GHC.Read.Read s, Data.Typeable.Internal.Typeable s) => Control.Monad.State.Class.MonadState (GHC.Base.Maybe s) (XMonad.Util.WindowState.StateQuery s) -- | Internal utility functions for storing Strings with the root window. -- -- Used for global state like IORefs with string keys, but more latency, -- persistent between xmonad restarts. module XMonad.Util.StringProp type StringProp = String -- | Get the name of a string property and returns it as a Maybe. getStringProp :: (MonadIO m) => Display -> StringProp -> m (Maybe [Char]) -- | Set the value of a string property. setStringProp :: (MonadIO m) => Display -> StringProp -> [Char] -> m () -- | Given a property name, returns its contents as a list. It uses the -- empty list as default value. getStringListProp :: (MonadIO m) => Display -> StringProp -> m [String] -- | Given a property name and a list, sets the value of this property with -- the list given as argument. setStringListProp :: (MonadIO m) => Display -> StringProp -> [String] -> m () -- | Implements a --replace behavior outside of core. module XMonad.Util.Replace -- | replace must be run before xmonad starts to signals to -- compliant window managers that they must exit and let xmonad take -- over. replace :: IO () -- | Customized key bindings. -- -- (See also XMonad.Util.EZConfig in xmonad-contrib.) module XMonad.Util.CustomKeys -- | Customize def -- delete needless shortcuts and insert those you -- will use. customKeys :: (XConfig Layout -> [(KeyMask, KeySym)]) -> (XConfig Layout -> [((KeyMask, KeySym), X ())]) -> XConfig Layout -> Map (KeyMask, KeySym) (X ()) -- | General variant of customKeys: customize key bindings of -- third-party configuration. customKeysFrom :: XConfig l -> (XConfig Layout -> [(KeyMask, KeySym)]) -> (XConfig Layout -> [((KeyMask, KeySym), X ())]) -> XConfig Layout -> Map (KeyMask, KeySym) (X ()) -- | A layout similar to tall but with three columns. With 2560x1600 pixels -- this layout can be used for a huge main window and up to six -- reasonable sized slave windows. module XMonad.Layout.ThreeColumns -- | Arguments are nmaster, delta, fraction data ThreeCol a ThreeColMid :: !Int -> !Rational -> !Rational -> ThreeCol a [threeColNMaster] :: ThreeCol a -> !Int [threeColDelta] :: ThreeCol a -> !Rational [threeColFrac] :: ThreeCol a -> !Rational ThreeCol :: !Int -> !Rational -> !Rational -> ThreeCol a [threeColNMaster] :: ThreeCol a -> !Int [threeColDelta] :: ThreeCol a -> !Rational [threeColFrac] :: ThreeCol a -> !Rational instance GHC.Read.Read (XMonad.Layout.ThreeColumns.ThreeCol a) instance GHC.Show.Show (XMonad.Layout.ThreeColumns.ThreeCol a) instance XMonad.Core.LayoutClass XMonad.Layout.ThreeColumns.ThreeCol a -- | A stacking layout, like dishes but with the ability to resize master -- pane. Mostly useful on small screens. module XMonad.Layout.StackTile data StackTile a StackTile :: !Int -> !Rational -> !Rational -> StackTile a instance GHC.Read.Read (XMonad.Layout.StackTile.StackTile a) instance GHC.Show.Show (XMonad.Layout.StackTile.StackTile a) instance XMonad.Core.LayoutClass XMonad.Layout.StackTile.StackTile a -- | A spiral tiling layout. module XMonad.Layout.Spiral -- | A spiral layout. The parameter controls the size ratio between -- successive windows in the spiral. Sensible values range from 0 up to -- the aspect ratio of your monitor (often 4/3). -- -- By default, the spiral is counterclockwise, starting to the east. See -- also spiralWithDir. spiral :: Rational -> SpiralWithDir a -- | Create a spiral layout, specifying the starting cardinal direction, -- the spiral direction (clockwise or counterclockwise), and the size -- ratio. spiralWithDir :: Direction -> Rotation -> Rational -> SpiralWithDir a data Rotation CW :: Rotation CCW :: Rotation data Direction East :: Direction South :: Direction West :: Direction North :: Direction data SpiralWithDir a instance GHC.Show.Show (XMonad.Layout.Spiral.SpiralWithDir a) instance GHC.Read.Read (XMonad.Layout.Spiral.SpiralWithDir a) instance GHC.Show.Show XMonad.Layout.Spiral.Direction instance GHC.Read.Read XMonad.Layout.Spiral.Direction instance GHC.Enum.Enum XMonad.Layout.Spiral.Direction instance GHC.Classes.Eq XMonad.Layout.Spiral.Direction instance GHC.Show.Show XMonad.Layout.Spiral.Rotation instance GHC.Read.Read XMonad.Layout.Spiral.Rotation instance XMonad.Core.LayoutClass XMonad.Layout.Spiral.SpiralWithDir a -- | This is a completely pointless layout which acts like Microsoft's Flip -- 3D module XMonad.Layout.Roledex data Roledex a Roledex :: Roledex a instance GHC.Read.Read (XMonad.Layout.Roledex.Roledex a) instance GHC.Show.Show (XMonad.Layout.Roledex.Roledex a) instance XMonad.Core.LayoutClass XMonad.Layout.Roledex.Roledex Graphics.X11.Types.Window -- | More useful tiled layout that allows you to change a width/height of -- window. module XMonad.Layout.ResizableTile data ResizableTall a ResizableTall :: Int -> Rational -> Rational -> [Rational] -> ResizableTall a -- | number of master windows [_nmaster] :: ResizableTall a -> Int -- | change when resizing by Shrink, Expand, -- MirrorShrink, MirrorExpand [_delta] :: ResizableTall a -> Rational -- | width of master [_frac] :: ResizableTall a -> Rational -- | fraction to multiply the window height that would be given when -- divided equally. -- -- slave windows are assigned their modified heights in order, from top -- to bottom -- -- unspecified values are replaced by 1 [_slaves] :: ResizableTall a -> [Rational] data MirrorResize MirrorShrink :: MirrorResize MirrorExpand :: MirrorResize instance GHC.Read.Read (XMonad.Layout.ResizableTile.ResizableTall a) instance GHC.Show.Show (XMonad.Layout.ResizableTile.ResizableTall a) instance XMonad.Core.Message XMonad.Layout.ResizableTile.MirrorResize instance XMonad.Core.LayoutClass XMonad.Layout.ResizableTile.ResizableTall a -- | Configure layouts on a per-workspace basis: use layouts and apply -- layout modifiers selectively, depending on the workspace. module XMonad.Layout.PerWorkspace -- | Structure for representing a workspace-specific layout along with a -- layout for all other workspaces. We store the tags of workspaces to be -- matched, and the two layouts. We save the layout choice in the Bool, -- to be used to implement description. data PerWorkspace l1 l2 a -- | Specify one layout to use on a particular workspace, and another to -- use on all others. The second layout can be another call to -- onWorkspace, and so on. onWorkspace :: (LayoutClass l1 a, LayoutClass l2 a) => WorkspaceId -> (l1 a) -> (l2 a) -> PerWorkspace l1 l2 a -- | Specify one layout to use on a particular set of workspaces, and -- another to use on all other workspaces. onWorkspaces :: (LayoutClass l1 a, LayoutClass l2 a) => [WorkspaceId] -> (l1 a) -> (l2 a) -> PerWorkspace l1 l2 a -- | Specify a layout modifier to apply to a particular workspace; layouts -- on all other workspaces will remain unmodified. modWorkspace :: (LayoutClass l1 a, LayoutClass l2 a) => WorkspaceId -> (l2 a -> l1 a) -> l2 a -> PerWorkspace l1 l2 a -- | Specify a layout modifier to apply to a particular set of workspaces; -- layouts on all other workspaces will remain unmodified. modWorkspaces :: (LayoutClass l1 a, LayoutClass l2 a) => [WorkspaceId] -> (l2 a -> l1 a) -> l2 a -> PerWorkspace l1 l2 a instance (GHC.Show.Show (l1 a), GHC.Show.Show (l2 a)) => GHC.Show.Show (XMonad.Layout.PerWorkspace.PerWorkspace l1 l2 a) instance (GHC.Read.Read (l1 a), GHC.Read.Read (l2 a)) => GHC.Read.Read (XMonad.Layout.PerWorkspace.PerWorkspace l1 l2 a) instance (XMonad.Core.LayoutClass l1 a, XMonad.Core.LayoutClass l2 a, GHC.Show.Show a) => XMonad.Core.LayoutClass (XMonad.Layout.PerWorkspace.PerWorkspace l1 l2) a -- | Configure layouts based on the width of your screen; use your favorite -- multi-column layout for wide screens and a full-screen layout for -- small ones. module XMonad.Layout.PerScreen data PerScreen l1 l2 a ifWider :: (LayoutClass l1 a, LayoutClass l2 a) => Dimension -> (l1 a) -> (l2 a) -> PerScreen l1 l2 a instance (GHC.Show.Show (l1 a), GHC.Show.Show (l2 a)) => GHC.Show.Show (XMonad.Layout.PerScreen.PerScreen l1 l2 a) instance (GHC.Read.Read (l1 a), GHC.Read.Read (l2 a)) => GHC.Read.Read (XMonad.Layout.PerScreen.PerScreen l1 l2 a) instance (XMonad.Core.LayoutClass l1 a, XMonad.Core.LayoutClass l2 a, GHC.Show.Show a) => XMonad.Core.LayoutClass (XMonad.Layout.PerScreen.PerScreen l1 l2) a -- | Provides layout named OneBig. It places one (master) window at top -- left corner of screen, and other (slave) windows at top module XMonad.Layout.OneBig -- | Data type for layout data OneBig a OneBig :: Float -> Float -> OneBig a instance GHC.Show.Show (XMonad.Layout.OneBig.OneBig a) instance GHC.Read.Read (XMonad.Layout.OneBig.OneBig a) instance XMonad.Core.LayoutClass XMonad.Layout.OneBig.OneBig a -- | Dynamically apply and unapply transformers to your window layout. This -- can be used to rotate your window layout by 90 degrees, or to make the -- currently focused window occupy the whole screen ("zoom in") then undo -- the transformation ("zoom out"). module XMonad.Layout.MultiToggle -- | A class to identify custom transformers (and look up transforming -- functions by type). class (Eq t, Typeable t) => Transformer t a | t -> a transform :: (Transformer t a, LayoutClass l a) => t -> l a -> (forall l'. (LayoutClass l' a) => l' a -> (l' a -> l a) -> b) -> b -- | Toggle the specified layout transformer. data Toggle a Toggle :: t -> Toggle a -- | Prepend an element to a heterogeneous list. Used to build transformer -- tables for mkToggle. (??) :: a -> b -> HCons a b -- | Marks the end of a transformer list. data EOT EOT :: EOT -- | Construct a singleton transformer table. single :: a -> HCons a EOT -- | Construct a MultiToggle layout from a transformer table and a -- base layout. mkToggle :: (LayoutClass l a) => ts -> l a -> MultiToggle ts l a -- | Construct a MultiToggle layout from a single transformer and -- a base layout. mkToggle1 :: (LayoutClass l a) => t -> l a -> MultiToggle (HCons t EOT) l a class HList c a data HCons a b data MultiToggle ts l a instance (GHC.Show.Show a, GHC.Show.Show b) => GHC.Show.Show (XMonad.Layout.MultiToggle.HCons a b) instance (GHC.Read.Read a, GHC.Read.Read b) => GHC.Read.Read (XMonad.Layout.MultiToggle.HCons a b) instance GHC.Show.Show XMonad.Layout.MultiToggle.EOT instance GHC.Read.Read XMonad.Layout.MultiToggle.EOT instance (GHC.Show.Show ts, GHC.Show.Show (l a)) => GHC.Show.Show (XMonad.Layout.MultiToggle.MultiToggleS ts l a) instance (GHC.Read.Read ts, GHC.Read.Read (l a)) => GHC.Read.Read (XMonad.Layout.MultiToggle.MultiToggleS ts l a) instance Data.Typeable.Internal.Typeable a => XMonad.Core.Message (XMonad.Layout.MultiToggle.Toggle a) instance (XMonad.Core.LayoutClass l a, GHC.Read.Read (l a), XMonad.Layout.MultiToggle.HList ts a, GHC.Read.Read ts) => GHC.Read.Read (XMonad.Layout.MultiToggle.MultiToggle ts l a) instance (GHC.Show.Show ts, GHC.Show.Show (l a), XMonad.Core.LayoutClass l a) => GHC.Show.Show (XMonad.Layout.MultiToggle.MultiToggle ts l a) instance XMonad.Layout.MultiToggle.HList XMonad.Layout.MultiToggle.EOT w instance (XMonad.Layout.MultiToggle.Transformer a w, XMonad.Layout.MultiToggle.HList b w) => XMonad.Layout.MultiToggle.HList (XMonad.Layout.MultiToggle.HCons a b) w instance (Data.Typeable.Internal.Typeable a, GHC.Show.Show ts, XMonad.Layout.MultiToggle.HList ts a, XMonad.Core.LayoutClass l a) => XMonad.Core.LayoutClass (XMonad.Layout.MultiToggle.MultiToggle ts l) a -- | This layout tiles windows in a growing number of columns. The number -- of windows in each column can be controlled by messages. module XMonad.Layout.MultiColumns -- | Layout constructor. multiCol :: [Int] -> Int -> Rational -> Rational -> MultiCol a data MultiCol a instance GHC.Classes.Eq (XMonad.Layout.MultiColumns.MultiCol a) instance GHC.Read.Read (XMonad.Layout.MultiColumns.MultiCol a) instance GHC.Show.Show (XMonad.Layout.MultiColumns.MultiCol a) instance XMonad.Core.LayoutClass XMonad.Layout.MultiColumns.MultiCol a -- | A layout which gives each window a specified amount of screen space -- relative to the others. Compared to the Mosaic layout, this -- one divides the space in a more balanced way. module XMonad.Layout.MosaicAlt data MosaicAlt a MosaicAlt :: Params -> MosaicAlt a shrinkWindowAlt :: Window -> HandleWindowAlt expandWindowAlt :: Window -> HandleWindowAlt tallWindowAlt :: Window -> HandleWindowAlt wideWindowAlt :: Window -> HandleWindowAlt resetAlt :: HandleWindowAlt type Params = Map Window Param data Param data HandleWindowAlt instance GHC.Read.Read (XMonad.Layout.MosaicAlt.MosaicAlt a) instance GHC.Show.Show (XMonad.Layout.MosaicAlt.MosaicAlt a) instance GHC.Read.Read XMonad.Layout.MosaicAlt.Param instance GHC.Show.Show XMonad.Layout.MosaicAlt.Param instance GHC.Classes.Eq XMonad.Layout.MosaicAlt.HandleWindowAlt instance XMonad.Core.Message XMonad.Layout.MosaicAlt.HandleWindowAlt instance XMonad.Core.LayoutClass XMonad.Layout.MosaicAlt.MosaicAlt Graphics.X11.Types.Window -- | Based on MosaicAlt, but aspect ratio messages always change the aspect -- ratios, and rearranging the window stack changes the window sizes. module XMonad.Layout.Mosaic data Aspect Taller :: Aspect Wider :: Aspect Reset :: Aspect SlopeMod :: ([Rational] -> [Rational]) -> Aspect -- | The relative magnitudes (the sign is ignored) of the rational numbers -- in the second argument determine the relative areas that the windows -- receive. The first number represents the size of the master window, -- the second is for the next window in the stack, and so on. -- -- The list is extended with ++ repeat 1, so mosaic 1.5 -- [] is like a resizable grid. -- -- The first parameter is the multiplicative factor to use when -- responding to the Expand message. mosaic :: Rational -> [Rational] -> Mosaic a -- | These sample functions are meant to be applied to the list of window -- sizes through the SlopeMod message. changeMaster :: (Rational -> Rational) -> X () -- | Apply a function to the Rational that represents the currently focused -- window. -- -- Expand and Shrink messages are responded to with -- changeFocused (*delta) or changeFocused (delta/) -- where delta is the first argument to mosaic. -- -- This is exported because other functions (ex. const 1, -- (+1)) may be useful to apply to the current area. changeFocused :: (Rational -> Rational) -> X () data Mosaic a instance GHC.Show.Show (XMonad.Layout.Mosaic.Mosaic a) instance GHC.Read.Read (XMonad.Layout.Mosaic.Mosaic a) instance XMonad.Core.Message XMonad.Layout.Mosaic.Aspect instance XMonad.Core.LayoutClass XMonad.Layout.Mosaic.Mosaic a instance Data.Foldable.Foldable XMonad.Layout.Mosaic.Tree instance GHC.Base.Functor XMonad.Layout.Mosaic.Tree instance GHC.Base.Monoid (XMonad.Layout.Mosaic.Tree a) -- | A layout combinator that sends a specified number of windows to one -- rectangle and the rest to another. Each of these rectangles are given -- a layout that is used within them. This can be chained to provide an -- arbitrary number of rectangles. The layout combinator allows -- overlapping rectangles, but such layouts does not work well together -- with hinting (XMonad.Layout.LayoutHints, -- XMonad.Layout.HintedGrid etc.) module XMonad.Layout.LayoutBuilder -- | Use the specified layout in the described area for N windows and send -- the rest of the windows to the next layout in the chain. It is -- possible to supply an alternative area that will then be used instead, -- if there are no windows to send to the next layout. layoutN :: (Read a, Eq a, LayoutClass l1 a, LayoutClass l2 a, LayoutClass l3 a) => Int -> SubBox -> Maybe SubBox -> l1 a -> LayoutN l2 l3 a -> LayoutN l1 (LayoutN l2 l3) a -- | As layoutN, but the number of windows is given relative to the total -- number of windows remaining to be handled. The first argument is how -- much to change the ratio when using IncLayoutN, and the second is the -- initial ratio. layoutR :: (Read a, Eq a, LayoutClass l1 a, LayoutClass l2 a, LayoutClass l3 a) => Rational -> Rational -> SubBox -> Maybe SubBox -> l1 a -> LayoutN l2 l3 a -> LayoutN l1 (LayoutN l2 l3) a -- | Use the specified layout in the described area for all remaining -- windows. layoutAll :: (Read a, Eq a, LayoutClass l1 a) => SubBox -> l1 a -> LayoutN l1 Full a -- | Change the number of windows handled by the focused layout. data IncLayoutN IncLayoutN :: Int -> IncLayoutN -- | The absolute or relative measures used to describe the area a layout -- should be placed in. For negative absolute values the total remaining -- space will be added. For sizes, the remaining space will also be added -- for zeroes. Relative values are applied on the remaining space after -- the top-left corner of the box have been removed. data SubMeasure Abs :: Int -> SubMeasure Rel :: Rational -> SubMeasure -- | A box to place a layout in. The stored values are xpos, ypos, width -- and height. data SubBox SubBox :: SubMeasure -> SubMeasure -> SubMeasure -> SubMeasure -> SubBox -- | Create a box with only absolute measurements. If the values are -- negative, the total remaining space will be added. For sizes it will -- also be added for zeroes. absBox :: Int -> Int -> Int -> Int -> SubBox -- | Create a box with only relative measurements. relBox :: Rational -> Rational -> Rational -> Rational -> SubBox -- | Use one layout in the specified area for a number of windows and -- possibly let another layout handle the rest. data LayoutN l1 l2 a instance (GHC.Read.Read a, GHC.Read.Read (l1 a), GHC.Read.Read (l2 a)) => GHC.Read.Read (XMonad.Layout.LayoutBuilder.LayoutN l1 l2 a) instance (GHC.Show.Show a, GHC.Show.Show (l1 a), GHC.Show.Show (l2 a)) => GHC.Show.Show (XMonad.Layout.LayoutBuilder.LayoutN l1 l2 a) instance GHC.Read.Read XMonad.Layout.LayoutBuilder.SubBox instance GHC.Show.Show XMonad.Layout.LayoutBuilder.SubBox instance GHC.Read.Read XMonad.Layout.LayoutBuilder.SubMeasure instance GHC.Show.Show XMonad.Layout.LayoutBuilder.SubMeasure instance XMonad.Core.Message XMonad.Layout.LayoutBuilder.IncLayoutN instance (XMonad.Core.LayoutClass l1 a, XMonad.Core.LayoutClass l2 a, GHC.Read.Read a, GHC.Show.Show a, GHC.Classes.Eq a, Data.Typeable.Internal.Typeable a) => XMonad.Core.LayoutClass (XMonad.Layout.LayoutBuilder.LayoutN l1 l2) a -- | Provides IfMax layout, which will run one layout if there are maximum -- N windows on workspace, and another layout, when number of windows is -- greater than N. module XMonad.Layout.IfMax data IfMax l1 l2 w IfMax :: Int -> (l1 w) -> (l2 w) -> IfMax l1 l2 w -- | Layout itself ifMax :: (LayoutClass l1 w, LayoutClass l2 w) => Int -> l1 w -> l2 w -> IfMax l1 l2 w instance (GHC.Show.Show (l1 w), GHC.Show.Show (l2 w)) => GHC.Show.Show (XMonad.Layout.IfMax.IfMax l1 l2 w) instance (GHC.Read.Read (l1 w), GHC.Read.Read (l2 w)) => GHC.Read.Read (XMonad.Layout.IfMax.IfMax l1 l2 w) instance (XMonad.Core.LayoutClass l1 a, XMonad.Core.LayoutClass l2 a) => XMonad.Core.LayoutClass (XMonad.Layout.IfMax.IfMax l1 l2) a -- | A not so simple layout that attempts to put all windows in a square -- grid while obeying their size hints. module XMonad.Layout.HintedGrid -- | Automatic mirroring of hinted layouts doesn't work very well, so this -- Grid comes with built-in mirroring. Grid False is the -- normal layout, Grid True is the mirrored variant (rotated by -- 90 degrees). data Grid a Grid :: Bool -> Grid a GridRatio :: Double -> Bool -> Grid a -- | The internal function for computing the grid layout. arrange :: Double -> Bool -> Rectangle -> [Window] -> X [(Window, Rectangle)] defaultRatio :: Double instance GHC.Show.Show (XMonad.Layout.HintedGrid.Grid a) instance GHC.Read.Read (XMonad.Layout.HintedGrid.Grid a) instance XMonad.Core.LayoutClass XMonad.Layout.HintedGrid.Grid Graphics.X11.Types.Window -- | A very simple layout. The simplest, afaik. module XMonad.Layout.Simplest data Simplest a Simplest :: Simplest a instance GHC.Read.Read (XMonad.Layout.Simplest.Simplest a) instance GHC.Show.Show (XMonad.Layout.Simplest.Simplest a) instance XMonad.Core.LayoutClass XMonad.Layout.Simplest.Simplest a -- | Two layouts: one is a variant of the Grid layout that allows the -- desired aspect ratio of windows to be specified. The other is like -- Tall but places a grid with fixed number of rows and columns in the -- master area and uses an aspect-ratio-specified layout for the slaves. module XMonad.Layout.GridVariants -- | The geometry change message understood by the master grid data ChangeMasterGridGeom -- | Change the number of master rows IncMasterRows :: !Int -> ChangeMasterGridGeom -- | Change the number of master columns IncMasterCols :: !Int -> ChangeMasterGridGeom -- | Set the number of master rows to absolute value SetMasterRows :: !Int -> ChangeMasterGridGeom -- | Set the number of master columns to absolute value SetMasterCols :: !Int -> ChangeMasterGridGeom -- | Set the fraction of the screen used by the master grid SetMasterFraction :: !Rational -> ChangeMasterGridGeom -- | Geometry change messages understood by Grid and SplitGrid data ChangeGridGeom SetGridAspect :: !Rational -> ChangeGridGeom ChangeGridAspect :: !Rational -> ChangeGridGeom -- | Grid layout. The parameter is the desired x:y aspect ratio of windows data Grid a Grid :: !Rational -> Grid a -- | TallGrid layout. Parameters are -- --
-- import XMonad.Hooks.SetWMName ---- -- Then edit your startupHook: -- --
-- startupHook = setWMName "LG3D" ---- -- For details on the problems with running Java GUI programs in -- non-reparenting WMs, see -- http://bugs.sun.com/bugdatabase/view_bug.do?bug_id=6429775 and -- related bugs. -- -- Setting WM name to "compiz" does not solve the problem, because of yet -- another bug in AWT code (related to insets). For LG3D insets are -- explicitly set to 0, while for other WMs the insets are "guessed" and -- the algorithm fails miserably by guessing absolutely bogus values. -- -- For detailed instructions on editing your hooks, see -- XMonad.Doc.Extending#4. module XMonad.Hooks.SetWMName -- | sets WM name setWMName :: String -> X () -- | Implemented in your logHook, Java swing applications will not -- misbehave when it comes to taking and losing focus. -- -- This has been done by taking the patch in -- http://code.google.com/p/xmonad/issues/detail?id=177 and -- refactoring it so that it can be included in -- ~/.xmonad/xmonad.hs. -- --
-- conf' =
-- conf {
-- logHook = takeTopFocus
-- }
--
-- | Deprecated: XMonad.Hooks.ICCCMFocus: xmonad>0.10 core merged
-- issue 177
module XMonad.Hooks.ICCCMFocus
-- | Common non-predefined atoms
atom_WM_TAKE_FOCUS :: X Atom
takeFocusX :: Window -> X ()
-- | The value to add to your log hook configuration.
takeTopFocus :: X ()
-- | Module to apply a ManageHook to an already-mapped window when a
-- property changes. This would commonly be used to match browser windows
-- by title, since the final title will only be set after (a) the window
-- is mapped, (b) its document has been loaded, (c) all load-time scripts
-- have run. (Don't blame browsers for this; it's inherent in HTML and
-- the DOM. And changing title dynamically is explicitly permitted by
-- ICCCM and EWMH; you don't really want to have your editor window
-- umapped/remapped to show the current document and modified state in
-- the titlebar, do you?)
--
-- This is a handleEventHook that triggers on a PropertyChange event. It
-- currently ignores properties being removed, in part because you can't
-- do anything useful in a ManageHook involving nonexistence of a
-- property.
module XMonad.Hooks.DynamicProperty
-- | Run a ManageHook when a specific property is changed on a
-- window. Note that this will run on any window which changes the
-- property, so you should be very specific in your MansgeHook
-- matching (lots of windows change their titles on the fly!):
--
-- dynamicPropertyChange WM_NAME (className =? Iceweasel
-- && title =? "whatever" --> doShift "2")
--
-- Note that the fixity of (-->) won't allow it to be mixed with ($),
-- so you can't use the obvious $ shorthand.
--
-- -- dynamicPropertyChange "WM_NAME" $ title =? "Foo" --> doFloat -- won't work! ---- -- Consider instead phrasing it like any other ManageHook: -- --
-- , handleEventHook = dynamicPropertyChange "WM_NAME" myDynHook <+> handleEventHook baseConfig
--
-- {- ... -}
--
-- myDynHook = composeAll [...]
--
dynamicPropertyChange :: String -> ManageHook -> Event -> X All
-- | A shorthand for the most common case, dynamic titles
dynamicTitle :: ManageHook -> Event -> X All
-- | Module to dump window information for diagnostic/debugging purposes.
-- See XMonad.Hooks.DebugEvents and XMonad.Hooks.DebugStack
-- for practical uses.
module XMonad.Util.DebugWindow
-- | Output a window by ID in hex, decimal, its ICCCM resource name and
-- class, and its title if available. Also indicate override_redirect
-- with an exclamation mark, and wrap in brackets if it is unmapped or
-- withdrawn.
debugWindow :: Window -> X String
-- | Dump the state of the StackSet. A logHook and
-- handleEventHook are also provided.
module XMonad.Hooks.DebugStack
-- | Print the state of the current window stack for the current workspace
-- to stderr, which for most installations goes to
-- ~/.xsession-errors. XMonad.Util.DebugWindow is used to
-- display the individual windows.
debugStack :: X ()
-- | Print the state of the current window stack for all workspaces to
-- stderr, which for most installations goes to
-- ~/.xsession-errors. XMonad.Util.DebugWindow is used to
-- display the individual windows.
debugStackFull :: X ()
-- | Dump the state of the current workspace in the StackSet as a
-- multiline String.
debugStackString :: X String
-- | Dump the state of all workspaces in the StackSet as a
-- multiline String. @@@ this is in stackset order, which is
-- roughly lru-ish
debugStackFullString :: X String
-- | debugStack packaged as a logHook. (Currently this is
-- identical.)
debugStackLogHook :: X ()
-- | 'debugStackFull packaged as a logHook. (Currently this is
-- identical.)
debugStackFullLogHook :: X ()
-- | debugStack packaged as a handleEventHook. You almost
-- certainly do not want to use this unconditionally, as it will cause
-- massive amounts of output and possibly slow xmonad down
-- severely.
debugStackEventHook :: Event -> X All
-- | debugStackFull packaged as a handleEventHook. You almost
-- certainly do not want to use this unconditionally, as it will cause
-- massive amounts of output and possibly slow xmonad down
-- severely.
debugStackFullEventHook :: Event -> X All
-- | A debugging module to track key events, useful when you can't tell
-- whether xmonad is processing some or all key events.
module XMonad.Hooks.DebugKeyEvents
-- | Print key events to stderr for debugging
debugKeyEvents :: Event -> X All
-- | Module to dump diagnostic information about X11 events received by
-- xmonad. This is incomplete due to Event being
-- incomplete and not providing information about a number of events, and
-- enforcing artificial constraints on others (for example
-- ClientMessage); the X11 package will require a
-- number of changes to fix these problems.
module XMonad.Hooks.DebugEvents
-- | Event hook to dump all received events. You should probably not use
-- this unconditionally; it will produce massive amounts of output.
debugEventsHook :: Event -> X All
instance Control.Monad.Reader.Class.MonadReader XMonad.Hooks.DebugEvents.Decode XMonad.Hooks.DebugEvents.Decoder
instance Control.Monad.State.Class.MonadState XMonad.Hooks.DebugEvents.DecodeState XMonad.Hooks.DebugEvents.Decoder
instance Control.Monad.IO.Class.MonadIO XMonad.Hooks.DebugEvents.Decoder
instance GHC.Base.Monad XMonad.Hooks.DebugEvents.Decoder
instance GHC.Base.Applicative XMonad.Hooks.DebugEvents.Decoder
instance GHC.Base.Functor XMonad.Hooks.DebugEvents.Decoder
-- | A layout that splits the screen horizontally and shows two windows.
-- The left window is always the master window, and the right is either
-- the currently focused window or the second window in layout order.
module XMonad.Layout.TwoPane
data TwoPane a
TwoPane :: Rational -> Rational -> TwoPane a
instance GHC.Read.Read (XMonad.Layout.TwoPane.TwoPane a)
instance GHC.Show.Show (XMonad.Layout.TwoPane.TwoPane a)
instance XMonad.Core.LayoutClass XMonad.Layout.TwoPane.TwoPane a
-- | Divide a single screen into multiple screens.
module XMonad.Layout.LayoutScreens
-- | Modify all screens.
layoutScreens :: LayoutClass l Int => Int -> l Int -> X ()
-- | Modify current screen.
layoutSplitScreen :: LayoutClass l Int => Int -> l Int -> X ()
fixedLayout :: [Rectangle] -> FixedLayout a
data FixedLayout a
instance GHC.Show.Show (XMonad.Layout.LayoutScreens.FixedLayout a)
instance GHC.Read.Read (XMonad.Layout.LayoutScreens.FixedLayout a)
instance XMonad.Core.LayoutClass XMonad.Layout.LayoutScreens.FixedLayout a
-- | A gapless tiled layout that attempts to obey window size hints, rather
-- than simply ignoring them.
module XMonad.Layout.HintedTile
data HintedTile a
HintedTile :: !Int -> !Rational -> !Rational -> !Alignment -> !Orientation -> HintedTile a
-- | number of windows in the master pane
[nmaster] :: HintedTile a -> !Int
-- | how much to change when resizing
[delta] :: HintedTile a -> !Rational
-- | ratio between master/nonmaster panes
[frac] :: HintedTile a -> !Rational
-- | Where to place windows that are smaller than their preordained
-- rectangles.
[alignment] :: HintedTile a -> !Alignment
-- | Tall or Wide (mirrored) layout?
[orientation] :: HintedTile a -> !Orientation
data Orientation
-- | Lay out windows similarly to Mirror tiled.
Wide :: Orientation
-- | Lay out windows similarly to tiled.
Tall :: Orientation
data Alignment
TopLeft :: Alignment
Center :: Alignment
BottomRight :: Alignment
instance GHC.Read.Read (XMonad.Layout.HintedTile.HintedTile a)
instance GHC.Show.Show (XMonad.Layout.HintedTile.HintedTile a)
instance GHC.Classes.Ord XMonad.Layout.HintedTile.Alignment
instance GHC.Classes.Eq XMonad.Layout.HintedTile.Alignment
instance GHC.Read.Read XMonad.Layout.HintedTile.Alignment
instance GHC.Show.Show XMonad.Layout.HintedTile.Alignment
instance GHC.Classes.Ord XMonad.Layout.HintedTile.Orientation
instance GHC.Classes.Eq XMonad.Layout.HintedTile.Orientation
instance GHC.Read.Read XMonad.Layout.HintedTile.Orientation
instance GHC.Show.Show XMonad.Layout.HintedTile.Orientation
instance XMonad.Core.LayoutClass XMonad.Layout.HintedTile.HintedTile Graphics.X11.Types.Window
-- | A module to toggle between two layouts.
module XMonad.Layout.ToggleLayouts
toggleLayouts :: (LayoutClass lt a, LayoutClass lf a) => lt a -> lf a -> ToggleLayouts lt lf a
data ToggleLayout
ToggleLayout :: ToggleLayout
Toggle :: String -> ToggleLayout
data ToggleLayouts lt lf a
instance GHC.Show.Show XMonad.Layout.ToggleLayouts.ToggleLayout
instance GHC.Read.Read XMonad.Layout.ToggleLayouts.ToggleLayout
instance (GHC.Show.Show (lt a), GHC.Show.Show (lf a)) => GHC.Show.Show (XMonad.Layout.ToggleLayouts.ToggleLayouts lt lf a)
instance (GHC.Read.Read (lt a), GHC.Read.Read (lf a)) => GHC.Read.Read (XMonad.Layout.ToggleLayouts.ToggleLayouts lt lf a)
instance XMonad.Core.Message XMonad.Layout.ToggleLayouts.ToggleLayout
instance (XMonad.Core.LayoutClass lt a, XMonad.Core.LayoutClass lf a) => XMonad.Core.LayoutClass (XMonad.Layout.ToggleLayouts.ToggleLayouts lt lf) a
-- | A layout that splits the screen into a square area and the rest of the
-- screen. This is probably only ever useful in combination with
-- XMonad.Layout.Combo. It sticks one window in a square region,
-- and makes the rest of the windows live with what's left (in a
-- full-screen sense).
module XMonad.Layout.Square
data Square a
Square :: Square a
instance GHC.Show.Show (XMonad.Layout.Square.Square a)
instance GHC.Read.Read (XMonad.Layout.Square.Square a)
instance XMonad.Core.LayoutClass XMonad.Layout.Square.Square a
-- | A simple layout that attempts to put all windows in a square grid.
module XMonad.Layout.Grid
data Grid a
Grid :: Grid a
GridRatio :: Double -> Grid a
arrange :: Double -> Rectangle -> [a] -> [(a, Rectangle)]
defaultRatio :: Double
instance GHC.Show.Show (XMonad.Layout.Grid.Grid a)
instance GHC.Read.Read (XMonad.Layout.Grid.Grid a)
instance XMonad.Core.LayoutClass XMonad.Layout.Grid.Grid a
-- | A module for setting the default mouse cursor.
--
-- Some ideas shamelessly stolen from Nils Schweinsberg; thanks!
module XMonad.Util.Cursor
-- | Set the default (root) cursor
setDefaultCursor :: Glyph -> X ()
-- | This module fixes some of the keybindings for the francophone among
-- you who use a BEPO keyboard layout. Based on XMonad.Config.Azerty
module XMonad.Config.Bepo
bepoConfig :: XConfig (Choose Tall (Choose (Mirror Tall) Full))
bepoKeys :: XConfig l -> Map (KeyMask, KeySym) (X ())
-- | This module fixes some of the keybindings for the francophone among
-- you who use an AZERTY keyboard layout. Config stolen from TeXitoi's
-- config on the wiki.
module XMonad.Config.Azerty
azertyConfig :: XConfig (Choose Tall (Choose (Mirror Tall) Full))
azertyKeys :: XConfig l -> Map (KeyMask, KeySym) (X ())
-- | LayoutClass that puts non-focused windows in ribbons at the top and
-- bottom of the screen.
module XMonad.Layout.Accordion
data Accordion a
Accordion :: Accordion a
instance GHC.Show.Show (XMonad.Layout.Accordion.Accordion a)
instance GHC.Read.Read (XMonad.Layout.Accordion.Accordion a)
instance XMonad.Core.LayoutClass XMonad.Layout.Accordion.Accordion Graphics.X11.Types.Window
-- | A module for writing easy layout modifiers, which do not define a
-- layout in and of themselves, but modify the behavior of or add new
-- functionality to other layouts. If you ever find yourself writing a
-- layout which takes another layout as a parameter, chances are you
-- should be writing a LayoutModifier instead!
--
-- In case it is not clear, this module is not intended to help you
-- configure xmonad, it is to help you write other extension modules. So
-- get hacking!
module XMonad.Layout.LayoutModifier
class (Show (m a), Read (m a)) => LayoutModifier m a where modifyLayout _ w r = runLayout w r modifyLayoutWithUpdate m w r = flip (,) Nothing `fmap` modifyLayout m w r handleMess m mess | Just Hide <- fromMessage mess = doUnhook | Just ReleaseResources <- fromMessage mess = doUnhook | otherwise = return $ pureMess m mess where doUnhook = do { unhook m; return Nothing } handleMessOrMaybeModifyIt m mess = do { mm' <- handleMess m mess; return (Left `fmap` mm') } pureMess _ _ = Nothing redoLayout m r ms wrs = do { hook m; return $ pureModifier m r ms wrs } pureModifier _ _ _ wrs = (wrs, Nothing) hook _ = return () unhook _ = return () modifierDescription = const "" modifyDescription m l = modifierDescription m <> description l where "" <> x = x x <> y = x ++ " " ++ y
-- | modifyLayout allows you to intercept a call to runLayout
-- before it is called on the underlying layout, in order to
-- perform some effect in the X monad, and/or modify some of the
-- parameters before passing them on to the runLayout method of
-- the underlying layout.
--
-- The default implementation of modifyLayout simply calls
-- runLayout on the underlying layout.
modifyLayout :: (LayoutModifier m a, LayoutClass l a) => m a -> Workspace WorkspaceId (l a) a -> Rectangle -> X ([(a, Rectangle)], Maybe (l a))
-- | Similar to modifyLayout, but this function also allows you
-- update the state of your layout modifier(the second value in the outer
-- tuple).
--
-- If both modifyLayoutWithUpdate and redoLayout return a
-- modified state of the layout modifier, redoLayout takes
-- precedence. If this function returns a modified state, this state will
-- internally be used in the subsequent call to redoLayout as
-- well.
modifyLayoutWithUpdate :: (LayoutModifier m a, LayoutClass l a) => m a -> Workspace WorkspaceId (l a) a -> Rectangle -> X (([(a, Rectangle)], Maybe (l a)), Maybe (m a))
-- | handleMess allows you to spy on messages to the underlying
-- layout, in order to have an effect in the X monad, or alter the layout
-- modifier state in some way (by returning Just nm, where
-- nm is a new modifier). In all cases, the underlying layout
-- will also receive the message as usual, after the message has been
-- processed by handleMess.
--
-- If you wish to possibly modify a message before it reaches the
-- underlying layout, you should use handleMessOrMaybeModifyIt
-- instead. If you do not need to modify messages or have access to the X
-- monad, you should use pureMess instead.
--
-- The default implementation of handleMess calls unhook
-- when receiving a Hide or ReleaseResources method (after
-- which it returns Nothing), and otherwise passes the message
-- on to pureMess.
handleMess :: LayoutModifier m a => m a -> SomeMessage -> X (Maybe (m a))
-- | handleMessOrMaybeModifyIt allows you to intercept messages sent
-- to the underlying layout, in order to have an effect in the X monad,
-- alter the layout modifier state, or produce a modified message to be
-- passed on to the underlying layout.
--
-- The default implementation of handleMessOrMaybeModifyIt simply
-- passes on the message to handleMess.
handleMessOrMaybeModifyIt :: LayoutModifier m a => m a -> SomeMessage -> X (Maybe (Either (m a) SomeMessage))
-- | pureMess allows you to spy on messages sent to the underlying
-- layout, in order to possibly change the layout modifier state.
--
-- The default implementation of pureMess ignores messages sent to
-- it, and returns Nothing (causing the layout modifier to
-- remain unchanged).
pureMess :: LayoutModifier m a => m a -> SomeMessage -> Maybe (m a)
-- | redoLayout allows you to intercept a call to runLayout
-- on workspaces with at least one window, after it is called on
-- the underlying layout, in order to perform some effect in the X monad,
-- possibly return a new layout modifier, and/or modify the results of
-- runLayout before returning them.
--
-- If you don't need access to the X monad, use pureModifier
-- instead. Also, if the behavior you need can be cleanly separated into
-- an effect in the X monad, followed by a pure transformation of the
-- results of runLayout, you should consider implementing
-- hook and pureModifier instead of redoLayout.
--
-- On empty workspaces, the Stack is Nothing.
--
-- The default implementation of redoLayout calls hook and
-- then pureModifier.
redoLayout :: LayoutModifier m a => m a -> Rectangle -> Maybe (Stack a) -> [(a, Rectangle)] -> X ([(a, Rectangle)], Maybe (m a))
-- | pureModifier allows you to intercept a call to runLayout
-- after it is called on the underlying layout, in order to modify
-- the list of window/rectangle pairings it has returned, and/or return a
-- new layout modifier.
--
-- The default implementation of pureModifier returns the window
-- rectangles unmodified.
pureModifier :: LayoutModifier m a => m a -> Rectangle -> Maybe (Stack a) -> [(a, Rectangle)] -> ([(a, Rectangle)], Maybe (m a))
-- | hook is called by the default implementation of
-- redoLayout, and as such represents an X action which is to be
-- run each time runLayout is called on the underlying layout,
-- after runLayout has completed. Of course, if you
-- override redoLayout, then hook will not be called unless
-- you explicitly call it.
--
-- The default implementation of hook is return () (i.e.,
-- it has no effect).
hook :: LayoutModifier m a => m a -> X ()
-- | unhook is called by the default implementation of
-- handleMess upon receiving a Hide or a
-- ReleaseResources message.
--
-- The default implementation, of course, does nothing.
unhook :: LayoutModifier m a => m a -> X ()
-- | modifierDescription is used to give a String description to
-- this layout modifier. It is the empty string by default; you should
-- only override this if it is important that the presence of the layout
-- modifier be displayed in text representations of the layout (for
-- example, in the status bar of a XMonad.Hooks.DynamicLog user).
modifierDescription :: LayoutModifier m a => m a -> String
-- | modifyDescription gives a String description for the entire
-- layout (modifier + underlying layout). By default, it is derived from
-- the concatenation of the modifierDescription with the
-- description of the underlying layout, with a "smart space" in
-- between (the space is not included if the modifierDescription
-- is empty).
modifyDescription :: (LayoutModifier m a, LayoutClass l a) => m a -> l a -> String
-- | A ModifiedLayout is simply a container for a layout modifier
-- combined with an underlying layout. It is, of course, itself a layout
-- (i.e. an instance of LayoutClass).
data ModifiedLayout m l a
ModifiedLayout :: (m a) -> (l a) -> ModifiedLayout m l a
instance (GHC.Show.Show (m a), GHC.Show.Show (l a)) => GHC.Show.Show (XMonad.Layout.LayoutModifier.ModifiedLayout m l a)
instance (GHC.Read.Read (m a), GHC.Read.Read (l a)) => GHC.Read.Read (XMonad.Layout.LayoutModifier.ModifiedLayout m l a)
instance (XMonad.Layout.LayoutModifier.LayoutModifier m a, XMonad.Core.LayoutClass l a) => XMonad.Core.LayoutClass (XMonad.Layout.LayoutModifier.ModifiedLayout m l) a
-- | Make a given layout display without borders. This is useful for
-- full-screen or tabbed layouts, where you don't really want to waste a
-- couple of pixels of real estate just to inform yourself that the
-- visible window has focus.
module XMonad.Layout.NoBorders
-- | Removes all window borders from the specified layout.
noBorders :: LayoutClass l Window => l Window -> ModifiedLayout WithBorder l Window
-- | Removes the borders from a window under one of the following
-- conditions:
--
-- -- data MyAmbiguity = MyAmbiguity deriving (Read, Show) ---- --
-- instance SetsAmbiguous MyAmbiguity where -- hiddens _ wset mst wrs = otherHiddens Screen \\ otherHiddens OnlyFloat -- where otherHiddens p = hiddens p wset mst wrs ---- -- The above example is redundant, because you can have the same result -- with: -- --
-- layoutHook = lessBorders (Combine Difference Screen OnlyFloat) (Tall 1 0.5 0.03 ||| ... ) ---- -- To get the same result as smartBorders: -- --
-- layoutHook = lessBorders Never (Tall 1 0.5 0.03 ||| ...) ---- -- This indirect method is required to keep the Read and -- Show for ConfigurableBorder so that xmonad can serialize state. class SetsAmbiguous p hiddens :: SetsAmbiguous p => p -> WindowSet -> Maybe (Stack Window) -> [(Window, Rectangle)] -> [Window] -- | In order of increasing ambiguity (less borders more frequently), where -- subsequent constructors add additional cases where borders are not -- drawn than their predecessors. These behaviors make most sense with -- with multiple screens: for single screens, Never or -- smartBorders makes more sense. data Ambiguity -- | This constructor is used to combine the borderless windows provided by -- the SetsAmbiguous instances from two other Ambiguity data -- types. Combine :: With -> Ambiguity -> Ambiguity -> Ambiguity -- | Only remove borders on floating windows that cover the whole screen OnlyFloat :: Ambiguity -- | Never remove borders when ambiguous: this is the same as smartBorders Never :: Ambiguity -- | Focus in an empty screens does not count as ambiguous. EmptyScreen :: Ambiguity -- | No borders on full when all other screens have borders. OtherIndicated :: Ambiguity -- | Borders are never drawn on singleton screens. With this one you really -- need another way such as a statusbar to detect focus. Screen :: Ambiguity -- | Used to indicate to the SetsAmbiguous instance for -- Ambiguity how two lists should be combined. data With -- | uses union Union :: With -- | uses \\ Difference :: With -- | uses intersect Intersection :: With type SmartBorder = ConfigurableBorder Ambiguity data WithBorder a data ConfigurableBorder p w instance GHC.Show.Show XMonad.Layout.NoBorders.Ambiguity instance GHC.Read.Read XMonad.Layout.NoBorders.Ambiguity instance GHC.Show.Show XMonad.Layout.NoBorders.With instance GHC.Read.Read XMonad.Layout.NoBorders.With instance (GHC.Show.Show p, GHC.Show.Show w) => GHC.Show.Show (XMonad.Layout.NoBorders.ConfigurableBorder p w) instance (GHC.Read.Read p, GHC.Read.Read w) => GHC.Read.Read (XMonad.Layout.NoBorders.ConfigurableBorder p w) instance GHC.Show.Show a => GHC.Show.Show (XMonad.Layout.NoBorders.WithBorder a) instance GHC.Read.Read a => GHC.Read.Read (XMonad.Layout.NoBorders.WithBorder a) instance XMonad.Layout.LayoutModifier.LayoutModifier XMonad.Layout.NoBorders.WithBorder Graphics.X11.Types.Window instance (GHC.Read.Read p, GHC.Show.Show p, XMonad.Layout.NoBorders.SetsAmbiguous p) => XMonad.Layout.LayoutModifier.LayoutModifier (XMonad.Layout.NoBorders.ConfigurableBorder p) Graphics.X11.Types.Window instance XMonad.Layout.NoBorders.SetsAmbiguous XMonad.Layout.NoBorders.Ambiguity -- | BoringWindows is an extension to allow windows to be marked boring module XMonad.Layout.BoringWindows boringWindows :: (LayoutClass l a, Eq a) => l a -> ModifiedLayout BoringWindows l a -- | Mark windows that are not given rectangles as boring boringAuto :: (LayoutClass l a, Eq a) => l a -> ModifiedLayout BoringWindows l a markBoring :: X () clearBoring :: X () focusUp :: X () focusDown :: X () focusMaster :: X () -- | UpdateBoring is sent before attempting to view another boring window, -- so that layouts have a chance to mark boring windows. data UpdateBoring UpdateBoring :: UpdateBoring data BoringMessage Replace :: String -> [Window] -> BoringMessage Merge :: String -> [Window] -> BoringMessage data BoringWindows a instance GHC.Read.Read a => GHC.Read.Read (XMonad.Layout.BoringWindows.BoringWindows a) instance GHC.Show.Show a => GHC.Show.Show (XMonad.Layout.BoringWindows.BoringWindows a) instance GHC.Show.Show XMonad.Layout.BoringWindows.BoringMessage instance GHC.Read.Read XMonad.Layout.BoringWindows.BoringMessage instance XMonad.Core.Message XMonad.Layout.BoringWindows.BoringMessage instance XMonad.Core.Message XMonad.Layout.BoringWindows.UpdateBoring instance XMonad.Layout.LayoutModifier.LayoutModifier XMonad.Layout.BoringWindows.BoringWindows Graphics.X11.Types.Window -- | A helper module to visualize the process of dragging a window by -- making it follow the mouse cursor. See -- XMonad.Layout.WindowSwitcherDecoration for a module that makes -- use of this. module XMonad.Layout.DraggingVisualizer draggingVisualizer :: LayoutClass l Window => l Window -> ModifiedLayout DraggingVisualizer l Window data DraggingVisualizerMsg DraggingWindow :: Window -> Rectangle -> DraggingVisualizerMsg DraggingStopped :: DraggingVisualizerMsg data DraggingVisualizer a instance GHC.Classes.Eq XMonad.Layout.DraggingVisualizer.DraggingVisualizerMsg instance GHC.Show.Show (XMonad.Layout.DraggingVisualizer.DraggingVisualizer a) instance GHC.Read.Read (XMonad.Layout.DraggingVisualizer.DraggingVisualizer a) instance XMonad.Core.Message XMonad.Layout.DraggingVisualizer.DraggingVisualizerMsg instance XMonad.Layout.LayoutModifier.LayoutModifier XMonad.Layout.DraggingVisualizer.DraggingVisualizer Graphics.X11.Types.Window -- | Provides layout modifier AutoMaster. It separates screen in two parts -- - master and slave. Size of slave area automatically changes depending -- on number of slave windows. module XMonad.Layout.AutoMaster -- | User interface function autoMaster :: LayoutClass l a => Int -> Float -> l a -> ModifiedLayout AutoMaster l a -- | Data type for layout modifier data AutoMaster a instance GHC.Show.Show (XMonad.Layout.AutoMaster.AutoMaster a) instance GHC.Read.Read (XMonad.Layout.AutoMaster.AutoMaster a) instance GHC.Classes.Eq w => XMonad.Layout.LayoutModifier.LayoutModifier XMonad.Layout.AutoMaster.AutoMaster w -- | Find a maximum empty rectangle around floating windows and use that -- area to display non-floating windows. module XMonad.Layout.AvoidFloats -- | Avoid floating windows unless the resulting area for windows would be -- too small. In that case, use the whole screen as if this layout -- modifier wasn't there. No windows are avoided by default, they need to -- be added using signals. avoidFloats :: l a -> ModifiedLayout AvoidFloats l a -- | Avoid floating windows unless the resulting area for windows would be -- too small. In that case, use the whole screen as if this layout -- modifier wasn't there. avoidFloats' :: Int -> Int -> Bool -> l a -> ModifiedLayout AvoidFloats l a -- | Change the state of the whole avoid float layout modifier. data AvoidFloatMsg -- | Toggle between avoiding all or only selected. AvoidFloatToggle :: AvoidFloatMsg -- | Set if all all floating windows should be avoided. AvoidFloatSet :: Bool -> AvoidFloatMsg -- | Clear the set of windows to specifically avoid. AvoidFloatClearItems :: AvoidFloatMsg -- | Change the state of the avoid float layout modifier conserning a -- specific window. data AvoidFloatItemMsg a -- | Add a window to always avoid. AvoidFloatAddItem :: a -> AvoidFloatItemMsg a -- | Stop always avoiding selected window. AvoidFloatRemoveItem :: a -> AvoidFloatItemMsg a -- | Toggle between always avoiding selected window. AvoidFloatToggleItem :: a -> AvoidFloatItemMsg a instance GHC.Show.Show a => GHC.Show.Show (XMonad.Layout.AvoidFloats.AvoidFloats a) instance (GHC.Classes.Ord a, GHC.Read.Read a) => GHC.Read.Read (XMonad.Layout.AvoidFloats.AvoidFloats a) instance XMonad.Core.Message XMonad.Layout.AvoidFloats.AvoidFloatMsg instance Data.Typeable.Internal.Typeable a => XMonad.Core.Message (XMonad.Layout.AvoidFloats.AvoidFloatItemMsg a) instance XMonad.Layout.LayoutModifier.LayoutModifier XMonad.Layout.AvoidFloats.AvoidFloats Graphics.X11.Types.Window -- | Two layout modifiers. centerMaster places master window at center, on -- top of all other windows, which are managed by base layout. -- topRightMaster is similar, but places master window in top right -- corner instead of center. module XMonad.Layout.CenteredMaster -- | Modifier that puts master window in center, other windows in -- background are managed by given layout centerMaster :: LayoutClass l a => l a -> ModifiedLayout CenteredMaster l a -- | Modifier that puts master window in top right corner, other windows in -- background are managed by given layout topRightMaster :: LayoutClass l a => l a -> ModifiedLayout TopRightMaster l a -- | Data type for LayoutModifier data CenteredMaster a data TopRightMaster a instance GHC.Show.Show (XMonad.Layout.CenteredMaster.TopRightMaster a) instance GHC.Read.Read (XMonad.Layout.CenteredMaster.TopRightMaster a) instance GHC.Show.Show (XMonad.Layout.CenteredMaster.CenteredMaster a) instance GHC.Read.Read (XMonad.Layout.CenteredMaster.CenteredMaster a) instance XMonad.Layout.LayoutModifier.LayoutModifier XMonad.Layout.CenteredMaster.CenteredMaster Graphics.X11.Types.Window instance XMonad.Layout.LayoutModifier.LayoutModifier XMonad.Layout.CenteredMaster.TopRightMaster Graphics.X11.Types.Window -- | Layout modifier that can modify the description of its underlying -- layout on a (hopefully) flexible way. module XMonad.Layout.Renamed -- | Apply a list of Rename values to a layout, from left to right. renamed :: [Rename a] -> l a -> ModifiedLayout Rename l a -- | The available renaming operations data Rename a -- | Remove a number of characters from the left CutLeft :: Int -> Rename a -- | Remove a number of characters from the right CutRight :: Int -> Rename a -- | Add a string on the right Append :: String -> Rename a -- | Add a string on the left Prepend :: String -> Rename a -- | Remove a number of words from the left CutWordsLeft :: Int -> Rename a -- | Remove a number of words from the right CutWordsRight :: Int -> Rename a -- | Add a string to the right, prepending a space to it if necessary AppendWords :: String -> Rename a -- | Add a string to the left, appending a space to it if necessary PrependWords :: String -> Rename a -- | Repace with another wtring Replace :: String -> Rename a -- | Apply a list of modifications in left-to-right order Chain :: [Rename a] -> Rename a instance GHC.Classes.Eq (XMonad.Layout.Renamed.Rename a) instance GHC.Read.Read (XMonad.Layout.Renamed.Rename a) instance GHC.Show.Show (XMonad.Layout.Renamed.Rename a) instance XMonad.Layout.LayoutModifier.LayoutModifier XMonad.Layout.Renamed.Rename a -- | A module for assigning a name to a given layout. Deprecated, use -- XMonad.Layout.Renamed instead. module XMonad.Layout.Named -- | (Deprecated) Rename a layout. named :: String -> l a -> ModifiedLayout Rename l a -- | (Deprecated) Remove the first word of the name. nameTail :: l a -> ModifiedLayout Rename l a -- | Provides message "escaping" and filtering facilities which help -- control complex nested layouts. module XMonad.Layout.MessageControl -- | the Ignore layout modifier. Prevents its inner layout from receiving -- messages of a certain type. data Ignore m l w -- | Applies the Ignore layout modifier to a layout, blocking all messages -- of the same type as the one passed as its first argument. ignore :: (Message m, LayoutClass l w) => m -> l w -> (Ignore m l w) -- | the UnEscape layout modifier. Listens to EscapedMessages and -- sends their nested message to the inner layout. data UnEscape w -- | Applies the UnEscape layout modifier to a layout. unEscape :: LayoutClass l w => l w -> ModifiedLayout UnEscape l w -- | Data type for an escaped message. Send with escape. newtype EscapedMessage Escape :: SomeMessage -> EscapedMessage -- | Creates an EscapedMessage. escape :: Message m => m -> EscapedMessage instance GHC.Read.Read (XMonad.Layout.MessageControl.UnEscape w) instance GHC.Show.Show (XMonad.Layout.MessageControl.UnEscape w) instance GHC.Read.Read (l w) => GHC.Read.Read (XMonad.Layout.MessageControl.Ignore m l w) instance GHC.Show.Show (l w) => GHC.Show.Show (XMonad.Layout.MessageControl.Ignore m l w) instance (XMonad.Core.Message m, XMonad.Core.LayoutClass l w) => XMonad.Core.LayoutClass (XMonad.Layout.MessageControl.Ignore m l) w instance XMonad.Layout.LayoutModifier.LayoutModifier XMonad.Layout.MessageControl.UnEscape a instance XMonad.Core.Message XMonad.Layout.MessageControl.EscapedMessage -- | Similar to XMonad.Layout.Minimize but completely removes -- windows from the window set so XMonad.Layout.BoringWindows -- isn't necessary. Perfect companion to -- XMonad.Layout.BinarySpacePartition since it can be used to move -- windows to another part of the BSP tree. module XMonad.Layout.Hidden -- | Messages for the HiddenWindows layout modifier. data HiddenMsg -- | Hide a window. HideWindow :: Window -> HiddenMsg -- | Restore window (FILO). PopNewestHiddenWindow :: HiddenMsg -- | Restore window (FIFO). PopOldestHiddenWindow :: HiddenMsg -- | Apply the HiddenWindows layout modifier. hiddenWindows :: LayoutClass l Window => l Window -> ModifiedLayout HiddenWindows l Window -- | Remove the given window from the current layout. It is placed in list -- of hidden windows so it can be restored later. hideWindow :: Window -> X () -- | Restore a previously hidden window. Using this function will treat the -- list of hidden windows as a FIFO queue. That is, the first window -- hidden will be restored. popOldestHiddenWindow :: X () -- | Restore a previously hidden window. Using this function will treat the -- list of hidden windows as a FILO queue. That is, the most recently -- hidden window will be restored. popNewestHiddenWindow :: X () instance GHC.Classes.Eq XMonad.Layout.Hidden.HiddenMsg instance GHC.Read.Read (XMonad.Layout.Hidden.HiddenWindows a) instance GHC.Show.Show (XMonad.Layout.Hidden.HiddenWindows a) instance XMonad.Core.Message XMonad.Layout.Hidden.HiddenMsg instance XMonad.Layout.LayoutModifier.LayoutModifier XMonad.Layout.Hidden.HiddenWindows Graphics.X11.Types.Window -- | Layout modfier suitable for workspace with multi-windowed instant -- messenger (like Psi or Tkabber). module XMonad.Layout.IM -- | Most of the property constructors are quite self-explaining. data Property Title :: String -> Property ClassName :: String -> Property Resource :: String -> Property -- | WM_WINDOW_ROLE property Role :: String -> Property -- | WM_CLIENT_MACHINE property Machine :: String -> Property And :: Property -> Property -> Property Or :: Property -> Property -> Property Not :: Property -> Property Const :: Bool -> Property -- | This is for compatibility with old configs only and will be removed in -- future versions! data IM a IM :: Rational -> Property -> IM a -- | Modifier which converts given layout to IM-layout (with dedicated -- space for roster and original layout for chat windows) withIM :: LayoutClass l a => Rational -> Property -> l a -> ModifiedLayout AddRoster l a -- | IM layout modifier applied to the Grid layout gridIM :: Rational -> Property -> ModifiedLayout AddRoster Grid a -- | Data type for LayoutModifier which converts given layout to IM-layout -- (with dedicated space for the roster and original layout for chat -- windows) data AddRoster a instance GHC.Show.Show (XMonad.Layout.IM.IM a) instance GHC.Read.Read (XMonad.Layout.IM.IM a) instance GHC.Show.Show (XMonad.Layout.IM.AddRoster a) instance GHC.Read.Read (XMonad.Layout.IM.AddRoster a) instance XMonad.Layout.LayoutModifier.LayoutModifier XMonad.Layout.IM.AddRoster Graphics.X11.Types.Window instance XMonad.Core.LayoutClass XMonad.Layout.IM.IM Graphics.X11.Types.Window -- | A layout modifier that limits the number of windows that can be shown. -- See XMonad.Layout.Minimize for manually setting hidden windows. module XMonad.Layout.LimitWindows -- | Only display the first n windows. limitWindows :: Int -> l a -> ModifiedLayout LimitWindows l a -- | Only display n windows around the focused window. This makes -- sense with layouts that arrange windows linearily, like -- Accordion. limitSlice :: Int -> l a -> ModifiedLayout LimitWindows l a -- | Only display the first m windows and r others. The -- IncMasterN message will change m, as well as passing -- it onto the underlying layout. limitSelect :: Int -> Int -> l a -> ModifiedLayout Selection l a increaseLimit :: X () decreaseLimit :: X () setLimit :: Int -> X () data LimitWindows a data Selection a instance GHC.Classes.Eq (XMonad.Layout.LimitWindows.Selection a) instance GHC.Show.Show (XMonad.Layout.LimitWindows.Selection a) instance GHC.Read.Read (XMonad.Layout.LimitWindows.Selection a) instance GHC.Show.Show (XMonad.Layout.LimitWindows.LimitWindows a) instance GHC.Read.Read (XMonad.Layout.LimitWindows.LimitWindows a) instance GHC.Show.Show XMonad.Layout.LimitWindows.SliceStyle instance GHC.Read.Read XMonad.Layout.LimitWindows.SliceStyle instance XMonad.Core.Message XMonad.Layout.LimitWindows.LimitChange instance XMonad.Layout.LayoutModifier.LayoutModifier XMonad.Layout.LimitWindows.LimitWindows a instance XMonad.Layout.LayoutModifier.LayoutModifier XMonad.Layout.LimitWindows.Selection a -- | Layout modfier that adds a master window to another layout. module XMonad.Layout.Master mastered :: (LayoutClass l a) => Rational -> Rational -> l a -> ModifiedLayout AddMaster l a fixMastered :: (LayoutClass l a) => Rational -> Rational -> l a -> ModifiedLayout FixMaster l a multimastered :: (LayoutClass l a) => Int -> Rational -> Rational -> l a -> ModifiedLayout AddMaster l a -- | Data type for LayoutModifier which converts given layout to a mastered -- layout data AddMaster a instance GHC.Read.Read (XMonad.Layout.Master.FixMaster a) instance GHC.Show.Show (XMonad.Layout.Master.FixMaster a) instance GHC.Read.Read (XMonad.Layout.Master.AddMaster a) instance GHC.Show.Show (XMonad.Layout.Master.AddMaster a) instance XMonad.Layout.LayoutModifier.LayoutModifier XMonad.Layout.Master.AddMaster Graphics.X11.Types.Window instance XMonad.Layout.LayoutModifier.LayoutModifier XMonad.Layout.Master.FixMaster Graphics.X11.Types.Window -- | Some convenient common instances of the Transformer class, for -- use with XMonad.Layout.MultiToggle. module XMonad.Layout.MultiToggle.Instances data StdTransformers -- | switch to Full layout FULL :: StdTransformers -- | switch to Full with no borders NBFULL :: StdTransformers -- | Mirror the current layout. MIRROR :: StdTransformers -- | Remove borders. NOBORDERS :: StdTransformers -- | Apply smart borders. SMARTBORDERS :: StdTransformers instance GHC.Classes.Eq XMonad.Layout.MultiToggle.Instances.StdTransformers instance GHC.Show.Show XMonad.Layout.MultiToggle.Instances.StdTransformers instance GHC.Read.Read XMonad.Layout.MultiToggle.Instances.StdTransformers instance XMonad.Layout.MultiToggle.Transformer XMonad.Layout.MultiToggle.Instances.StdTransformers Graphics.X11.Types.Window -- | Configure layouts on a per-host basis: use layouts and apply layout -- modifiers selectively, depending on the host. Heavily based on -- XMonad.Layout.PerWorkspace by Brent Yorgey. module XMonad.Layout.OnHost -- | Structure for representing a host-specific layout along with a layout -- for all other hosts. We store the names of hosts to be matched, and -- the two layouts. We save the layout choice in the Bool, to be used to -- implement description. data OnHost l1 l2 a -- | Specify one layout to use on a particular host, and another to use on -- all others. The second layout can be another call to onHost, -- and so on. onHost :: (LayoutClass l1 a, LayoutClass l2 a) => String -> (l1 a) -> (l2 a) -> OnHost l1 l2 a -- | Specify one layout to use on a particular set of hosts, and another to -- use on all other hosts. onHosts :: (LayoutClass l1 a, LayoutClass l2 a) => [String] -> (l1 a) -> (l2 a) -> OnHost l1 l2 a -- | Specify a layout modifier to apply on a particular host; layouts on -- all other hosts will remain unmodified. modHost :: (LayoutClass l a) => String -> (l a -> ModifiedLayout lm l a) -> l a -> OnHost (ModifiedLayout lm l) l a -- | Specify a layout modifier to apply on a particular set of hosts; -- layouts on all other hosts will remain unmodified. modHosts :: (LayoutClass l a) => [String] -> (l a -> ModifiedLayout lm l a) -> l a -> OnHost (ModifiedLayout lm l) l a instance (GHC.Show.Show (l1 a), GHC.Show.Show (l2 a)) => GHC.Show.Show (XMonad.Layout.OnHost.OnHost l1 l2 a) instance (GHC.Read.Read (l1 a), GHC.Read.Read (l2 a)) => GHC.Read.Read (XMonad.Layout.OnHost.OnHost l1 l2 a) instance (XMonad.Core.LayoutClass l1 a, XMonad.Core.LayoutClass l2 a, GHC.Show.Show a) => XMonad.Core.LayoutClass (XMonad.Layout.OnHost.OnHost l1 l2) a -- | Layout modifier that tracks focus in the tiled layer while the -- floating layer is in use. This is particularly helpful for tiled -- layouts where the focus determines what is visible. -- -- The relevant bugs are Issue 4 and 306: -- http://code.google.com/p/xmonad/issues/detail?id=4, -- http://code.google.com/p/xmonad/issues/detail?id=306 module XMonad.Layout.TrackFloating -- | Runs another layout with a remembered focus, provided: -- --
-- import XMonad.Hooks.ManageHelpers
-- main =
-- xmonad def{
-- ...
-- manageHook = composeOne [
-- isKDETrayWindow -?> doIgnore,
-- transience,
-- isFullscreen -?> doFullFloat,
-- resource =? "stalonetray" -?> doIgnore
-- ],
-- ...
-- }
--
module XMonad.Hooks.ManageHelpers
-- | Denotes a side of a screen. S stands for South, NE
-- for Northeast etc. C stands for Center.
data Side
SC :: Side
NC :: Side
CE :: Side
CW :: Side
SE :: Side
SW :: Side
NE :: Side
NW :: Side
C :: Side
-- | An alternative ManageHook composer. Unlike composeAll it
-- stops as soon as a candidate returns a Just value, effectively
-- running only the first match (whereas composeAll continues and
-- executes all matching rules).
composeOne :: [MaybeManageHook] -> ManageHook
-- | A helper operator for use in composeOne. It takes a condition
-- and an action; if the condition fails, it returns Nothing from
-- the Query so composeOne will go on and try the next
-- rule.
(-?>) :: Query Bool -> ManageHook -> MaybeManageHook
-- | q /=? x. if the result of q equals x, return False
(/=?) :: Eq a => Query a -> a -> Query Bool
-- | q <==? x. if the result of q equals x, return True grouped with q
(<==?) :: Eq a => Query a -> a -> Query (Match a)
-- | q </=? x. if the result of q notequals x, return True grouped with
-- q
(=?) :: Eq a => Query a -> a -> Query (Match a)
-- | A helper operator for use in composeAll. It takes a condition
-- and a function taking a grouped datum to action. If p is
-- true, it executes the resulting action.
(-->>) :: Query (Match a) -> (a -> ManageHook) -> ManageHook
-- | A helper operator for use in composeOne. It takes a condition
-- and a function taking a groupdatum to action. If p is true,
-- it executes the resulting action. If it fails, it returns
-- Nothing from the Query so composeOne will go on
-- and try the next rule.
(-?>>) :: Query (Match a) -> (a -> ManageHook) -> MaybeManageHook
-- | Return the current workspace
currentWs :: Query WorkspaceId
-- | Helper to check if a window property contains certain value.
isInProperty :: String -> String -> Query Bool
-- | A predicate to check whether a window is a KDE system tray icon.
isKDETrayWindow :: Query Bool
-- | A predicate to check whether a window wants to fill the whole screen.
-- See also doFullFloat.
isFullscreen :: Query Bool
-- | A predicate to check whether a window is a dialog.
isDialog :: Query Bool
pid :: Query (Maybe ProcessID)
-- | A predicate to check whether a window is Transient. It holds the
-- result which might be the window it is transient to or it might be
-- Nothing.
transientTo :: Query (Maybe Window)
-- | converts MaybeManageHooks to ManageHooks
maybeToDefinite :: MaybeManageHook -> ManageHook
-- | A ManageHook that may or may not have been executed; the outcome is
-- embedded in the Maybe
type MaybeManageHook = Query (Maybe (Endo WindowSet))
-- | A convenience MaybeManageHook that will check to see if a
-- window is transient, and then move it to its parent.
transience :: MaybeManageHook
-- | transience set to a ManageHook
transience' :: ManageHook
-- | Floats the new window in the given rectangle.
doRectFloat :: RationalRect -> ManageHook
-- | Floats the window and makes it use the whole screen. Equivalent to
-- doRectFloat $ RationalRect 0 0 1 1.
doFullFloat :: ManageHook
-- | Floats a new window with its original size, but centered.
doCenterFloat :: ManageHook
-- | Floats a new window with its original size on the specified side of a
-- screen
doSideFloat :: Side -> ManageHook
-- | Floats a new window with its original size, and its top left corner at
-- a specific point on the screen (both coordinates should be in the
-- range 0 to 1).
doFloatAt :: Rational -> Rational -> ManageHook
-- | Floats a new window using a rectangle computed as a function of the
-- rectangle that it would have used by default.
doFloatDep :: (RationalRect -> RationalRect) -> ManageHook
-- | Hides window and ignores it.
doHideIgnore :: ManageHook
-- | A grouping type, which can hold the outcome of a predicate Query. This
-- is analogous to group types in regular expressions. TODO: create a
-- better API for aggregating multiple Matches logically
data Match a
instance GHC.Classes.Eq XMonad.Hooks.ManageHelpers.Side
instance GHC.Show.Show XMonad.Hooks.ManageHelpers.Side
instance GHC.Read.Read XMonad.Hooks.ManageHelpers.Side
-- | Hooks for sending messages about fullscreen windows to layouts, and a
-- few example layout modifier that implement fullscreen windows.
module XMonad.Layout.Fullscreen
-- | Modifies your config to apply basic fullscreen support -- fullscreen
-- windows when they request it. Example usage:
--
--
-- main = xmonad
-- $ fullscreenSupport
-- $ defaultConfig { ... }
--
fullscreenSupport :: LayoutClass l Window => XConfig l -> XConfig (ModifiedLayout FullscreenFull l)
-- | Layout modifier that makes fullscreened window fill the entire screen.
fullscreenFull :: LayoutClass l a => l a -> ModifiedLayout FullscreenFull l a
-- | Layout modifier that makes the fullscreened window fill the entire
-- screen only if it is currently focused.
fullscreenFocus :: LayoutClass l a => l a -> ModifiedLayout FullscreenFocus l a
-- | As above, but the fullscreened window will fill the specified
-- rectangle instead of the entire screen.
fullscreenFullRect :: LayoutClass l a => RationalRect -> l a -> ModifiedLayout FullscreenFull l a
-- | As above, but the fullscreened window will fill the specified
-- rectangle instead of the entire screen.
fullscreenFocusRect :: LayoutClass l a => RationalRect -> l a -> ModifiedLayout FullscreenFocus l a
-- | Hackish layout modifier that makes floating fullscreened windows fill
-- the entire screen.
fullscreenFloat :: LayoutClass l a => l a -> ModifiedLayout FullscreenFloat l a
-- | As above, but the fullscreened window will fill the specified
-- rectangle instead of the entire screen.
fullscreenFloatRect :: LayoutClass l a => RationalRect -> l a -> ModifiedLayout FullscreenFloat l a
-- | The event hook required for the layout modifiers to work
fullscreenEventHook :: Event -> X All
-- | Manage hook that sets the fullscreen property for windows that are
-- initially fullscreen
fullscreenManageHook :: ManageHook
-- | A version of fullscreenManageHook that lets you specify your own query
-- to decide whether a window should be fullscreen.
fullscreenManageHookWith :: Query Bool -> ManageHook
-- | Messages that control the fullscreen state of the window.
-- AddFullscreen and RemoveFullscreen are sent to all layouts when a
-- window wants or no longer wants to be fullscreen. FullscreenChanged is
-- sent to the current layout after one of the above have been sent.
data FullscreenMessage
AddFullscreen :: Window -> FullscreenMessage
RemoveFullscreen :: Window -> FullscreenMessage
FullscreenChanged :: FullscreenMessage
data FullscreenFloat a
data FullscreenFocus a
data FullscreenFull a
instance GHC.Show.Show a => GHC.Show.Show (XMonad.Layout.Fullscreen.FullscreenFloat a)
instance (GHC.Classes.Ord a, GHC.Read.Read a) => GHC.Read.Read (XMonad.Layout.Fullscreen.FullscreenFloat a)
instance GHC.Show.Show a => GHC.Show.Show (XMonad.Layout.Fullscreen.FullscreenFocus a)
instance GHC.Read.Read a => GHC.Read.Read (XMonad.Layout.Fullscreen.FullscreenFocus a)
instance GHC.Show.Show a => GHC.Show.Show (XMonad.Layout.Fullscreen.FullscreenFull a)
instance GHC.Read.Read a => GHC.Read.Read (XMonad.Layout.Fullscreen.FullscreenFull a)
instance XMonad.Core.Message XMonad.Layout.Fullscreen.FullscreenMessage
instance XMonad.Layout.LayoutModifier.LayoutModifier XMonad.Layout.Fullscreen.FullscreenFull Graphics.X11.Types.Window
instance XMonad.Layout.LayoutModifier.LayoutModifier XMonad.Layout.Fullscreen.FullscreenFocus Graphics.X11.Types.Window
instance XMonad.Layout.LayoutModifier.LayoutModifier XMonad.Layout.Fullscreen.FullscreenFloat Graphics.X11.Types.Window
-- | Layout modifier for displaying some window (monitor) above other
-- windows.
module XMonad.Layout.Monitor
data Monitor a
Monitor :: Property -> Rectangle -> Bool -> String -> Bool -> Rational -> Monitor a
-- | property which uniquely identifies monitor window
[prop] :: Monitor a -> Property
-- | specifies where to put monitor
[rect] :: Monitor a -> Rectangle
-- | is it visible by default?
[visible] :: Monitor a -> Bool
-- | name of monitor (useful when we have many of them)
[name] :: Monitor a -> String
-- | is it shown on all layouts?
[persistent] :: Monitor a -> Bool
-- | opacity level
[opacity] :: Monitor a -> Rational
-- | Template for Monitor record. At least prop and
-- rect should be redefined. Default settings: visible is
-- True, persistent is False.
monitor :: Monitor a
-- | Most of the property constructors are quite self-explaining.
data Property
Title :: String -> Property
ClassName :: String -> Property
Resource :: String -> Property
-- | WM_WINDOW_ROLE property
Role :: String -> Property
-- | WM_CLIENT_MACHINE property
Machine :: String -> Property
And :: Property -> Property -> Property
Or :: Property -> Property -> Property
Not :: Property -> Property
Const :: Bool -> Property
-- | Messages without names affect all monitors. Messages with names affect
-- only monitors whose names match.
data MonitorMessage
ToggleMonitor :: MonitorMessage
ShowMonitor :: MonitorMessage
HideMonitor :: MonitorMessage
ToggleMonitorNamed :: String -> MonitorMessage
ShowMonitorNamed :: String -> MonitorMessage
HideMonitorNamed :: String -> MonitorMessage
-- | Hides window and ignores it.
doHideIgnore :: ManageHook
-- | ManageHook which demanages monitor window and applies opacity
-- settings.
manageMonitor :: Monitor a -> ManageHook
instance GHC.Classes.Eq XMonad.Layout.Monitor.MonitorMessage
instance GHC.Show.Show XMonad.Layout.Monitor.MonitorMessage
instance GHC.Read.Read XMonad.Layout.Monitor.MonitorMessage
instance GHC.Show.Show (XMonad.Layout.Monitor.Monitor a)
instance GHC.Read.Read (XMonad.Layout.Monitor.Monitor a)
instance XMonad.Core.Message XMonad.Layout.Monitor.MonitorMessage
instance XMonad.Layout.LayoutModifier.LayoutModifier XMonad.Layout.Monitor.Monitor Graphics.X11.Types.Window
-- | Provides functions for performing a given action on all windows of the
-- current workspace.
module XMonad.Actions.WithAll
-- | Un-float all floating windows on the current workspace.
sinkAll :: X ()
-- | Execute an X action for each window on the current workspace.
withAll :: (Window -> X ()) -> X ()
-- | Apply a function to all windows on the current workspace.
withAll' :: (Window -> WindowSet -> WindowSet) -> X ()
-- | Kill all the windows on the current workspace.
killAll :: X ()
-- | Provides a simple binding that pushes all floating windows on the
-- current workspace back into tiling. Note that the functionality of
-- this module has been folded into the more general
-- XMonad.Actions.WithAll; this module simply re-exports the
-- sinkAll function for backwards compatibility.
module XMonad.Actions.SinkAll
-- | Un-float all floating windows on the current workspace.
sinkAll :: X ()
-- | A module for setting up timers
module XMonad.Util.Timer
-- | Start a timer, which will send a ClientMessageEvent after some time
-- (in seconds).
startTimer :: Rational -> X TimerId
-- | Given a TimerId and an Event, run an action when the
-- Event has been sent by the timer specified by the
-- TimerId
handleTimer :: TimerId -> Event -> X (Maybe a) -> X (Maybe a)
type TimerId = Int
-- | This module implements a special kind of layout modifier, which when
-- applied to a layout, causes xmonad to stop all non-visible processes.
-- In a way, this is a sledge-hammer for applications that drain power.
-- For example, given a web browser on a stoppable workspace, once the
-- workspace is hidden the web browser will be stopped.
--
-- Note that the stopped application won't be able to communicate with
-- X11 clipboard. For this, the module actually stops applications after
-- a certain delay, giving a chance for a user to complete copy-paste
-- sequence. By default, the delay equals to 15 seconds, it is
-- configurable via Stoppable constructor.
--
-- The stoppable modifier prepends a mark (by default equals to
-- "Stoppable") to the layout description (alternatively, you can choose
-- your own mark and use it with Stoppable constructor). The
-- stoppable layout (identified by a mark) spans to multiple workspaces,
-- letting you to create groups of stoppable workspaces that only stop
-- processes when none of the workspaces are visible, and conversely,
-- unfreezing all processes even if one of the stoppable workspaces are
-- visible.
--
-- To stop the process we use signals, which works for most cases. For
-- processes that tinker with signal handling (debuggers), another
-- (Linux-centric) approach may be used. See
-- https://www.kernel.org/doc/Documentation/cgroups/freezer-subsystem.txt
module XMonad.Layout.Stoppable
-- | Data type for ModifiedLayout. The constructor lets you to specify a
-- custom mark/description modifier and a delay. You can also use
-- stoppable helper function.
data Stoppable a
Stoppable :: String -> Rational -> Maybe TimerId -> Stoppable a
[mark] :: Stoppable a -> String
[delay] :: Stoppable a -> Rational
[timer] :: Stoppable a -> Maybe TimerId
-- | Convert a layout to a stoppable layout using the default mark
-- ("Stoppable") and a delay of 15 seconds.
stoppable :: l a -> ModifiedLayout Stoppable l a
instance GHC.Read.Read (XMonad.Layout.Stoppable.Stoppable a)
instance GHC.Show.Show (XMonad.Layout.Stoppable.Stoppable a)
instance XMonad.Layout.LayoutModifier.LayoutModifier XMonad.Layout.Stoppable.Stoppable Graphics.X11.Types.Window
-- | An action to start terminals with a random background color
module XMonad.Actions.RandomBackground
-- | randomBg' produces a random hex number in the form
-- '#xxyyzz'
randomBg' :: (MonadIO m) => RandomColor -> m String
-- | randomBg starts a terminal with the background color taken
-- from randomBg'
--
-- This depends on the your terminal configuration field accepting
-- an argument like -bg '#ff0023'
randomBg :: RandomColor -> X ()
-- | RandomColor fixes constraints when generating random colors. All
-- parameters should be in the range 0 -- 0xff
data RandomColor
-- | specify the minimum and maximum lowest values for each color channel.
RGB :: Int -> Int -> RandomColor
-- | specify the saturation and value, leaving the hue random.
HSV :: Double -> Double -> RandomColor
-- | Alternate promote function for xmonad.
--
-- Moves the focused window to the master pane. All other windows retain
-- their order. If focus is in the master, swap it with the next window
-- in the stack. Focus stays in the master.
module XMonad.Actions.Promote
-- | Move the focused window to the master pane. All other windows retain
-- their order. If focus is in the master, swap it with the next windo in
-- the stack. Focus stays in the master.
promote :: X ()
-- | Manipulate screens ordered by physical location instead of ID
module XMonad.Actions.PhysicalScreens
-- | The type of the index of a screen by location
newtype PhysicalScreen
P :: Int -> PhysicalScreen
-- | Translate a physical screen index to a ScreenId
getScreen :: PhysicalScreen -> X (Maybe ScreenId)
-- | Switch to a given physical screen
viewScreen :: PhysicalScreen -> X ()
-- | Send the active window to a given physical screen
sendToScreen :: PhysicalScreen -> X ()
-- | Apply operation on a WindowSet with the WorkspaceId of the next screen
-- in the physical order as parameter.
onNextNeighbour :: (WorkspaceId -> WindowSet -> WindowSet) -> X ()
-- | Apply operation on a WindowSet with the WorkspaceId of the previous
-- screen in the physical order as parameter.
onPrevNeighbour :: (WorkspaceId -> WindowSet -> WindowSet) -> X ()
instance GHC.Real.Real XMonad.Actions.PhysicalScreens.PhysicalScreen
instance GHC.Real.Integral XMonad.Actions.PhysicalScreens.PhysicalScreen
instance GHC.Num.Num XMonad.Actions.PhysicalScreens.PhysicalScreen
instance GHC.Enum.Enum XMonad.Actions.PhysicalScreens.PhysicalScreen
instance GHC.Read.Read XMonad.Actions.PhysicalScreens.PhysicalScreen
instance GHC.Show.Show XMonad.Actions.PhysicalScreens.PhysicalScreen
instance GHC.Classes.Ord XMonad.Actions.PhysicalScreens.PhysicalScreen
instance GHC.Classes.Eq XMonad.Actions.PhysicalScreens.PhysicalScreen
-- | Define key-bindings on per-workspace basis.
module XMonad.Actions.PerWorkspaceKeys
-- | Uses supplied function to decide which action to run depending on
-- current workspace name.
chooseAction :: (String -> X ()) -> X ()
-- | If current workspace is listed, run appropriate action (only the first
-- match counts!) If it isn't listed, then run default action (marked
-- with empty string, ""), or do nothing if default isn't supplied.
bindOn :: [(String, X ())] -> X ()
-- | This module provides helper functions for dealing with window borders.
module XMonad.Actions.NoBorders
-- | Toggle the border of the currently focused window. To use it, add a
-- keybinding like so:
--
-- -- , ((modm, xK_g ), withFocused toggleBorder) --toggleBorder :: Window -> X () -- | Useful helper functions for amending the default configuration, and -- for parsing keybindings specified in a special (emacs-like) format. -- -- (See also XMonad.Util.CustomKeys in xmonad-contrib.) module XMonad.Util.EZConfig -- | Add or override keybindings from the existing set. Example use: -- --
-- main = xmonad $ def { terminal = "urxvt" }
-- `additionalKeys`
-- [ ((mod1Mask, xK_m ), spawn "echo 'Hi, mom!' | dzen2 -p 4")
-- , ((mod1Mask, xK_BackSpace), withFocused hide) -- N.B. this is an absurd thing to do
-- ]
--
--
-- This overrides the previous definition of mod-m.
--
-- Note that, unlike in xmonad 0.4 and previous, you can't use modMask to
-- refer to the modMask you configured earlier. You must specify mod1Mask
-- (or whichever), or add your own myModMask = mod1Mask line.
additionalKeys :: XConfig a -> [((ButtonMask, KeySym), X ())] -> XConfig a
-- | Like additionalKeys, except using short String key
-- descriptors like "M-m" instead of (modMask, xK_m),
-- as described in the documentation for mkKeymap. For example:
--
--
-- main = xmonad $ def { terminal = "urxvt" }
-- `additionalKeysP`
-- [ ("M-m", spawn "echo 'Hi, mom!' | dzen2 -p 4")
-- , ("M-<Backspace>", withFocused hide) -- N.B. this is an absurd thing to do
-- ]
--
additionalKeysP :: XConfig l -> [(String, X ())] -> XConfig l
-- | Remove standard keybindings you're not using. Example use:
--
--
-- main = xmonad $ def { terminal = "urxvt" }
-- `removeKeys` [(mod1Mask .|. shiftMask, n) | n <- [xK_1 .. xK_9]]
--
removeKeys :: XConfig a -> [(ButtonMask, KeySym)] -> XConfig a
-- | Like removeKeys, except using short String key
-- descriptors like "M-m" instead of (modMask, xK_m),
-- as described in the documentation for mkKeymap. For example:
--
--
-- main = xmonad $ def { terminal = "urxvt" }
-- `removeKeysP` ["M-S-" ++ [n] | n <- ['1'..'9']]
--
removeKeysP :: XConfig l -> [String] -> XConfig l
-- | Like additionalKeys, but for mouse bindings.
additionalMouseBindings :: XConfig a -> [((ButtonMask, Button), Window -> X ())] -> XConfig a
-- | Like removeKeys, but for mouse bindings.
removeMouseBindings :: XConfig a -> [(ButtonMask, Button)] -> XConfig a
-- | Given a config (used to determine the proper modifier key to use) and
-- a list of (String, X ()) pairs, create a key map by parsing
-- the key sequence descriptions contained in the Strings. The key
-- sequence descriptions are "emacs-style": M-, C-,
-- S-, and M#- denote mod, control, shift, and
-- mod1-mod5 (where # is replaced by the appropriate number)
-- respectively. Note that if you want to make a keybinding using 'alt'
-- even though you use a different key (like the 'windows' key) for
-- 'mod', you can use something like "M1-x" for alt+x (check the
-- output of xmodmap to see which mod key 'alt' is bound to).
-- Some special keys can also be specified by enclosing their name in
-- angle brackets.
--
-- For example, "M-C-x" denotes mod+ctrl+x;
-- "S-<Escape>" denotes shift-escape;
-- "M1-C-<Delete>" denotes alt+ctrl+delete (assuming alt
-- is bound to mod1, which is common).
--
-- Sequences of keys can also be specified by separating the key
-- descriptions with spaces. For example, "M-x y <Down>"
-- denotes the sequence of keys mod+x, y, down. Submaps (see
-- XMonad.Actions.Submap) will be automatically generated to
-- correctly handle these cases.
--
-- So, for example, a complete key map might be specified as
--
--
-- keys = \c -> mkKeymap c $
-- [ ("M-S-<Return>", spawn $ terminal c)
-- , ("M-x w", spawn "xmessage 'woohoo!'") -- type mod+x then w to pop up 'woohoo!'
-- , ("M-x y", spawn "xmessage 'yay!'") -- type mod+x then y to pop up 'yay!'
-- , ("M-S-c", kill)
-- ]
--
--
-- Alternatively, you can use additionalKeysP to automatically
-- create a keymap and add it to your config.
--
-- Here is a complete list of supported special keys. Note that a few
-- keys, such as the arrow keys, have synonyms. If there are other
-- special keys you would like to see supported, feel free to submit a
-- patch, or ask on the xmonad mailing list; adding special keys is quite
-- simple.
--
-- -- <Backspace> -- <Tab> -- <Return> -- <Pause> -- <Scroll_lock> -- <Sys_Req> -- <Print> -- <Escape>, <Esc> -- <Delete> -- <Home> -- <Left>, <L> -- <Up>, <U> -- <Right>, <R> -- <Down>, <D> -- <Page_Up> -- <Page_Down> -- <End> -- <Insert> -- <Break> -- <Space> -- <F1>-<F24> -- <KP_Space> -- <KP_Tab> -- <KP_Enter> -- <KP_F1> -- <KP_F2> -- <KP_F3> -- <KP_F4> -- <KP_Home> -- <KP_Left> -- <KP_Up> -- <KP_Right> -- <KP_Down> -- <KP_Prior> -- <KP_Page_Up> -- <KP_Next> -- <KP_Page_Down> -- <KP_End> -- <KP_Begin> -- <KP_Insert> -- <KP_Delete> -- <KP_Equal> -- <KP_Multiply> -- <KP_Add> -- <KP_Separator> -- <KP_Subtract> -- <KP_Decimal> -- <KP_Divide> -- <KP_0>-<KP_9> ---- -- Long list of multimedia keys. Please note that not all keys may be -- present in your particular setup although most likely they will do. -- --
-- <XF86ModeLock> -- <XF86MonBrightnessUp> -- <XF86MonBrightnessDown> -- <XF86KbdLightOnOff> -- <XF86KbdBrightnessUp> -- <XF86KbdBrightnessDown> -- <XF86Standby> -- <XF86AudioLowerVolume> -- <XF86AudioMute> -- <XF86AudioRaiseVolume> -- <XF86AudioPlay> -- <XF86AudioStop> -- <XF86AudioPrev> -- <XF86AudioNext> -- <XF86HomePage> -- <XF86Mail> -- <XF86Start> -- <XF86Search> -- <XF86AudioRecord> -- <XF86Calculator> -- <XF86Memo> -- <XF86ToDoList> -- <XF86Calendar> -- <XF86PowerDown> -- <XF86ContrastAdjust> -- <XF86RockerUp> -- <XF86RockerDown> -- <XF86RockerEnter> -- <XF86Back> -- <XF86Forward> -- <XF86Stop> -- <XF86Refresh> -- <XF86PowerOff> -- <XF86WakeUp> -- <XF86Eject> -- <XF86ScreenSaver> -- <XF86WWW> -- <XF86Sleep> -- <XF86Favorites> -- <XF86AudioPause> -- <XF86AudioMedia> -- <XF86MyComputer> -- <XF86VendorHome> -- <XF86LightBulb> -- <XF86Shop> -- <XF86History> -- <XF86OpenURL> -- <XF86AddFavorite> -- <XF86HotLinks> -- <XF86BrightnessAdjust> -- <XF86Finance> -- <XF86Community> -- <XF86AudioRewind> -- <XF86XF86BackForward> -- <XF86Launch0>-<XF86Launch9>, <XF86LaunchA>-<XF86LaunchF> -- <XF86ApplicationLeft> -- <XF86ApplicationRight> -- <XF86Book> -- <XF86CD> -- <XF86Calculater> -- <XF86Clear> -- <XF86Close> -- <XF86Copy> -- <XF86Cut> -- <XF86Display> -- <XF86DOS> -- <XF86Documents> -- <XF86Excel> -- <XF86Explorer> -- <XF86Game> -- <XF86Go> -- <XF86iTouch> -- <XF86LogOff> -- <XF86Market> -- <XF86Meeting> -- <XF86MenuKB> -- <XF86MenuPB> -- <XF86MySites> -- <XF86New> -- <XF86News> -- <XF86OfficeHome> -- <XF86Open> -- <XF86Option> -- <XF86Paste> -- <XF86Phone> -- <XF86Q> -- <XF86Reply> -- <XF86Reload> -- <XF86RotateWindows> -- <XF86RotationPB> -- <XF86RotationKB> -- <XF86Save> -- <XF86ScrollUp> -- <XF86ScrollDown> -- <XF86ScrollClick> -- <XF86Send> -- <XF86Spell> -- <XF86SplitScreen> -- <XF86Support> -- <XF86TaskPane> -- <XF86Terminal> -- <XF86Tools> -- <XF86Travel> -- <XF86UserPB> -- <XF86User1KB> -- <XF86User2KB> -- <XF86Video> -- <XF86WheelButton> -- <XF86Word> -- <XF86Xfer> -- <XF86ZoomIn> -- <XF86ZoomOut> -- <XF86Away> -- <XF86Messenger> -- <XF86WebCam> -- <XF86MailForward> -- <XF86Pictures> -- <XF86Music> -- <XF86TouchpadToggle> -- <XF86AudioMicMute> -- <XF86_Switch_VT_1>-<XF86_Switch_VT_12> -- <XF86_Ungrab> -- <XF86_ClearGrab> -- <XF86_Next_VMode> -- <XF86_Prev_VMode> --mkKeymap :: XConfig l -> [(String, X ())] -> Map (KeyMask, KeySym) (X ()) -- | Given a configuration record and a list of (key sequence description, -- action) pairs, check the key sequence descriptions for validity, and -- warn the user (via a popup xmessage window) of any unparseable or -- duplicate key sequences. This function is appropriate for adding to -- your startupHook, and you are highly encouraged to do so; -- otherwise, duplicate or unparseable keybindings will be silently -- ignored. -- -- For example, you might do something like this: -- --
-- main = xmonad $ myConfig
--
-- myKeymap = [("S-M-c", kill), ...]
-- myConfig = def {
-- ...
-- keys = \c -> mkKeymap c myKeymap
-- startupHook = return () >> checkKeymap myConfig myKeymap
-- ...
-- }
--
--
-- NOTE: the return () in the example above is very important!
-- Otherwise, you might run into problems with infinite mutual recursion:
-- the definition of myConfig depends on the definition of startupHook,
-- which depends on the definition of myConfig, ... and so on. Actually,
-- it's likely that the above example in particular would be OK without
-- the return (), but making myKeymap take
-- myConfig as a parameter would definitely lead to problems.
-- Believe me. It, uh, happened to my friend. In... a dream. Yeah. In any
-- event, the return () >> introduces enough laziness to
-- break the deadlock.
checkKeymap :: XConfig l -> [(String, a)] -> X ()
mkNamedKeymap :: XConfig l -> [(String, NamedAction)] -> [((KeyMask, KeySym), NamedAction)]
-- | Parse an unmodified basic key, like "x",
-- "F1", etc.
parseKey :: ReadP KeySym
-- | This is a draft of a brand new config syntax for xmonad. It aims to
-- be:
--
-- -- manageHook =: composeAll [className =? "MPlayer" --> doFloat, className =? "Gimp" --> doFloat] ---- -- To add more rules to this list, you can say, for instance: -- --
-- import XMonad.StackSet -- ... -- manageHook =+ (className =? "Emacs" --> doF kill) -- manageHook =+ (className =? "Vim" --> doF shiftMaster) ---- -- Note that operator precedence mandates the parentheses here. manageHook :: Summable ManageHook ManageHook (XConfig l) -- | Custom X event handler. Return All True if the default -- handler should also be run afterwards. Default does nothing. To add an -- event handler: -- --
-- import XMonad.Hooks.ServerMode -- ... -- handleEventHook =+ serverModeEventHook --handleEventHook :: Summable (Event -> X All) (Event -> X All) (XConfig l) -- | List of workspaces' names. Default: map show [1 .. 9 :: Int]. -- Adding appends to the end: -- --
-- workspaces =+ ["0"] ---- -- This is useless unless you also create keybindings for this. workspaces :: Summable [String] [String] (XConfig l) -- | The action to perform when the windows set is changed. This happens -- whenever focus change, a window is moved, etc. logHook =+ -- takes an X () and appends it via '(>>)'. For instance: -- --
-- import XMonad.Hooks.ICCCMFocus -- ... -- logHook =+ takeTopFocus ---- -- Note that if your expression is parametrically typed (e.g. of type -- MonadIO m => m ()), you'll need to explicitly annotate it, -- like so: -- --
-- logHook =+ (io $ putStrLn "Hello, world!" :: X ()) --logHook :: Summable (X ()) (X ()) (XConfig l) -- | The action to perform on startup. startupHook =+ takes an -- X () and appends it via '(>>)'. For instance: -- --
-- import XMonad.Hooks.SetWMName -- ... -- startupHook =+ setWMName "LG3D" ---- -- Note that if your expression is parametrically typed (e.g. of type -- MonadIO m => m ()), you'll need to explicitly annotate it, -- as documented in logHook. startupHook :: Summable (X ()) (X ()) (XConfig l) -- | The client events that xmonad is interested in. This is useful in -- combination with handleEventHook. Default: structureNotifyMask .|. -- enterWindowMask .|. propertyChangeMask -- --
-- clientMask =+ keyPressMask .|. keyReleaseMask --clientMask :: Summable EventMask EventMask (XConfig l) -- | The root events that xmonad is interested in. This is useful in -- combination with handleEventHook. Default: -- substructureRedirectMask .|. substructureNotifyMask .|. -- enterWindowMask .|. leaveWindowMask .|. structureNotifyMask .|. -- buttonPressMask rootMask :: Summable EventMask EventMask (XConfig l) class SummableClass s y | s -> y -- | This lets you add to an attribute. (=+) :: SummableClass s y => s c -> y -> Arr c c -- | Key bindings to X actions. Default: see `man xmonad`. -- keys takes a list of keybindings specified emacs-style, as -- documented in mkKeyMap. For example, to change the "kill -- window" key: -- --
-- keys =- ["M-S-c"]
-- keys =+ [("M-M1-x", kill)]
--
keys :: Keys (XConfig l)
-- | Mouse button bindings to an X actions on a window. Default: see
-- `man xmonad`. To make mod-scrollwheel switch
-- workspaces:
--
-- -- import XMonad.Actions.CycleWS (nextWS, prevWS) -- ... -- mouseBindings =+ [((mod4Mask, button4), const prevWS), -- ((mod4Mask, button5), const nextWS)] ---- -- Note that you need to specify the numbered mod-mask e.g. -- mod4Mask instead of just modMask. mouseBindings :: MouseBindings (XConfig l) class RemovableClass r y | r -> y -- | This lets you remove from an attribute. (=-) :: RemovableClass r y => r c -> y -> Arr c c -- | Configure workspaces through a Prime-like interface. Example: -- --
-- withWorkspaces $ do
-- wsKeys =+ ["0"]
-- wsActions =+ [("M-M1-", windows . swapWithCurrent)]
-- wsSetName 1 "mail"
--
--
-- This will set workspaces and add the necessary keybindings to
-- keys. Note that it won't remove old keybindings; it's just not
-- that clever.
withWorkspaces :: Arr WorkspaceConfig WorkspaceConfig -> Prime l l
-- | The list of workspace names, like workspaces but with two
-- differences:
--
--
-- [("M-", windows . W.greedyView),
-- ("M-S-", windows . W.shift)]
--
wsActions :: Summable [(String, String -> X ())] [(String, String -> X ())] WorkspaceConfig
-- | A convenience for just modifying one entry in wsNames, in case
-- you only want a few named workspaces. Example:
--
-- -- wsSetName 1 "mail" -- wsSetName 2 "web" --wsSetName :: Int -> String -> Arr WorkspaceConfig WorkspaceConfig -- | Configure screen keys through a Prime-like interface: -- --
-- withScreens $ do -- sKeys =: ["e", "r"] ---- -- This will add the necessary keybindings to keys. Note that it -- won't remove old keybindings; it's just not that clever. withScreens :: Arr ScreenConfig ScreenConfig -> Prime l l -- | The list of screen keys. These are combined with the modifiers in -- sActions to form the keybindings for navigating to workspaces. -- Default: ["w","e","r"]. sKeys :: Summable [String] [String] ScreenConfig -- | Mapping from key prefix to command. Its type is [(String, ScreenId -- -> X())]. Works the same as wsActions except for a -- different function type. -- -- Default: -- --
-- [("M-", windows . onScreens W.view),
-- ("M-S-", windows . onScreens W.shift)]
--
sActions :: Summable [(String, ScreenId -> X ())] [(String, ScreenId -> X ())] ScreenConfig
-- | Converts a stackset transformer parameterized on the workspace type
-- into one parameterized on the screen type. For example, you can use
-- onScreens W.view 0 to navigate to the workspace on the 0th
-- screen. If the screen id is not recognized, the returned transformer
-- acts as an identity function.
onScreens :: Eq s => (i -> StackSet i l a s sd -> StackSet i l a s sd) -> s -> StackSet i l a s sd -> StackSet i l a s sd
-- | Add a layout to the list of layouts choosable with mod-space. For
-- instance:
--
-- -- import XMonad.Layout.Tabbed -- ... -- addLayout simpleTabbed --addLayout :: (LayoutClass l Window, LayoutClass r Window) => r Window -> Prime l (Choose l r) -- | Reset the layoutHook from scratch. For instance, to get rid of the -- wide layout: -- --
-- resetLayout $ Tall 1 (3/100) (1/2) ||| Full ---- -- (The dollar is like an auto-closing parenthesis, so all the stuff to -- the right of it is treated like an argument to resetLayout.) resetLayout :: (LayoutClass r Window) => r Window -> Prime l r -- | Modify your layoutHook with some wrapper function. You -- probably want to call this after you're done calling addLayout. -- Example: -- --
-- import XMonad.Layout.NoBorders -- ... -- modifyLayout smartBorders --modifyLayout :: (LayoutClass r Window) => (l Window -> r Window) -> Prime l r -- | Replace the current XConfig with the given one. If you use -- this, you probably want it to be the first line of your config. startWith :: XConfig l' -> Prime l l' -- | Turns a pure function on XConfig into a Prime. apply :: (XConfig l -> XConfig l') -> Prime l l' -- | Turns an IO function on XConfig into a Prime. applyIO :: (XConfig l -> IO (XConfig l')) -> Prime l l' -- | A Prime is a function that transforms an XConfig. It's not a monad, -- but we turn on RebindableSyntax so we can abuse the pretty do -- notation. type Prime l l' = Arr (XConfig l) (XConfig l') -- | An Arr is a generalization of Prime. Don't reference the type, if you -- can avoid it. It might go away in the future. type Arr x y = x -> IO y -- | Composes two Arrs using >>= from Prelude. (>>) :: Arr x y -> Arr y z -> Arr x z -- | Because of RebindableSyntax, this is necessary to enable you to use -- if-then-else expressions. No need to call it directly. ifThenElse :: Bool -> a -> a -> a instance XMonad.Config.Prime.UpdateableClass s x y => XMonad.Config.Prime.SettableClass s x y instance XMonad.Config.Prime.UpdateableClass (XMonad.Config.Prime.Settable x) x x instance XMonad.Config.Prime.UpdateableClass (XMonad.Config.Prime.Summable x y) x x instance XMonad.Config.Prime.SummableClass (XMonad.Config.Prime.Summable x y) y instance XMonad.Config.Prime.SummableClass XMonad.Config.Prime.Keys [(GHC.Base.String, XMonad.Core.X ())] instance XMonad.Config.Prime.RemovableClass XMonad.Config.Prime.Keys [GHC.Base.String] instance XMonad.Config.Prime.SummableClass XMonad.Config.Prime.MouseBindings [((Graphics.X11.Types.ButtonMask, Graphics.X11.Types.Button), Graphics.X11.Types.Window -> XMonad.Core.X ())] instance XMonad.Config.Prime.RemovableClass XMonad.Config.Prime.MouseBindings [(Graphics.X11.Types.ButtonMask, Graphics.X11.Types.Button)] instance Data.Default.Class.Default XMonad.Config.Prime.WorkspaceConfig instance Data.Default.Class.Default XMonad.Config.Prime.ScreenConfig -- | Alternative to sendMessage that provides knowledge of whether -- the message was handled, and utility functions based on this facility. module XMonad.Actions.MessageFeedback -- | Behaves like sendMessage, but returns True of the message was -- handled by the layout, False otherwise. send :: Message a => a -> X Bool -- | Sends the first message, and if it was not handled, sends the second. -- Returns True if either message was handled, False otherwise. tryMessage :: (Message a, Message b) => a -> b -> X Bool tryMessage_ :: (Message a, Message b) => a -> b -> X () -- | Tries sending every message of the list in order until one of them is -- handled. Returns True if one of the messages was handled, False -- otherwise. tryInOrder :: [SomeMessage] -> X Bool tryInOrder_ :: [SomeMessage] -> X () -- | Convenience shorthand for SomeMessage. sm :: Message a => a -> SomeMessage sendSM :: SomeMessage -> X Bool sendSM_ :: SomeMessage -> X () -- | Utility functions for XMonad.Layout.Groups. module XMonad.Layout.Groups.Helpers -- | Swap the focused window with the previous one swapUp :: X () -- | Swap the focused window with the next one swapDown :: X () -- | Swap the focused window with the master window swapMaster :: X () -- | If the focused window is floating, focus the next floating window. -- otherwise, focus the next non-floating one. focusUp :: X () -- | If the focused window is floating, focus the next floating window. -- otherwise, focus the next non-floating one. focusDown :: X () -- | Move focus to the master window focusMaster :: X () -- | Move focus between the floating and non-floating layers toggleFocusFloat :: X () -- | Swap the focused group with the previous one swapGroupUp :: X () -- | Swap the focused group with the next one swapGroupDown :: X () -- | Swap the focused group with the master group swapGroupMaster :: X () -- | Move the focus to the previous group focusGroupUp :: X () -- | Move the focus to the next group focusGroupDown :: X () -- | Move the focus to the master group focusGroupMaster :: X () -- | Move the focused window to the previous group. The Bool -- argument determines what will be done if the focused window is in the -- very first group: Wrap back to the end (True), or create a new -- group before it (False). moveToGroupUp :: Bool -> X () -- | Move the focused window to the next group. The Bool argument -- determines what will be done if the focused window is in the very last -- group: Wrap back to the beginning (True), or create a new group -- after it (False). moveToGroupDown :: Bool -> X () -- | Move the focused window to a new group before the current one moveToNewGroupUp :: X () -- | Move the focused window to a new group after the current one moveToNewGroupDown :: X () -- | Split the focused group in two at the position of the focused window. splitGroup :: X () -- | Control workspaces on different screens (in xinerama mode). module XMonad.Actions.OnScreen -- | Run any function that modifies the stack on a given screen. This -- function will also need to know which Screen to focus after the -- function has been run. onScreen :: (WindowSet -> WindowSet) -> Focus -> ScreenId -> WindowSet -> WindowSet -- | A variation of onScreen which will take any X () -- function and run it on the given screen. Warning: This function will -- change focus even if the function it's supposed to run doesn't -- succeed. onScreen' :: X () -> Focus -> ScreenId -> X () -- | Focus data definitions data Focus -- | always focus the new screen FocusNew :: Focus -- | always keep the focus on the current screen FocusCurrent :: Focus -- | always focus tag i on the new stack FocusTag :: WorkspaceId -> Focus -- | focus tag i only if workspace with tag i is visible on the old stack FocusTagVisible :: WorkspaceId -> Focus -- | Switch to workspace i on screen sc. If i is -- visible use view to switch focus to the workspace i. viewOnScreen :: ScreenId -> WorkspaceId -> WindowSet -> WindowSet -- | Switch to workspace i on screen sc. If i is -- visible use greedyView to switch the current workspace with -- workspace i. greedyViewOnScreen :: ScreenId -> WorkspaceId -> WindowSet -> WindowSet -- | Switch to workspace i on screen sc. If i is -- visible do nothing. onlyOnScreen :: ScreenId -> WorkspaceId -> WindowSet -> WindowSet -- | toggleOrView as in XMonad.Actions.CycleWS for -- onScreen with view toggleOnScreen :: ScreenId -> WorkspaceId -> WindowSet -> WindowSet -- | toggleOrView from XMonad.Actions.CycleWS for -- onScreen with greedyView toggleGreedyOnScreen :: ScreenId -> WorkspaceId -> WindowSet -> WindowSet -- | This modules provides several commands to run an external process. It -- is composed of functions formerly defined in XMonad.Util.Dmenu -- (by Spencer Janssen), XMonad.Util.Dzen (by glasser@mit.edu) and -- XMonad.Util.RunInXTerm (by Andrea Rossato). module XMonad.Util.Run -- | Returns the output. runProcessWithInput :: MonadIO m => FilePath -> [String] -> String -> m String -- | Wait is in μ (microseconds) runProcessWithInputAndWait :: MonadIO m => FilePath -> [String] -> String -> Int -> m () -- | safeSpawn bypasses spawn, because spawn passes strings -- to /bin/sh to be interpreted as shell commands. This is often what one -- wants, but in many cases the passed string will contain shell -- metacharacters which one does not want interpreted as such (URLs -- particularly often have shell metacharacters like '&' in them). In -- this case, it is more useful to specify a file or program to be run -- and a string to give it as an argument so as to bypass the shell and -- be certain the program will receive the string as you typed it. -- -- Examples: -- --
-- , ((modm, xK_Print), unsafeSpawn "import -window root $HOME/xwd-$(date +%s)$$.png") -- , ((modm, xK_d ), safeSpawn "firefox" []) ---- -- Note that the unsafeSpawn example must be unsafe and not safe because -- it makes use of shell interpretation by relying on $HOME and -- interpolation, whereas the safeSpawn example can be safe because -- Firefox doesn't need any arguments if it is just being started. safeSpawn :: MonadIO m => FilePath -> [String] -> m () -- | Simplified safeSpawn; only takes a program (and no arguments): -- --
-- , ((modm, xK_d ), safeSpawnProg "firefox") --safeSpawnProg :: MonadIO m => FilePath -> m () -- | An alias for spawn; the name emphasizes that one is calling out -- to a Turing-complete interpreter which may do things one dislikes; for -- details, see safeSpawn. unsafeSpawn :: MonadIO m => String -> m () -- | Open a terminal emulator. The terminal emulator is specified in the -- default configuration as xterm by default. It is then asked to pass -- the shell a command with certain options. This is unsafe in the sense -- of unsafeSpawn runInTerm :: String -> String -> X () -- | Run a given program in the preferred terminal emulator; see -- runInTerm. This makes use of safeSpawn. safeRunInTerm :: String -> String -> X () -- | Multiplies by ONE MILLION, for functions that take microseconds. -- -- Use like: -- --
-- (5.5 `seconds`) ---- -- In GHC 7 and later, you must either enable the PostfixOperators -- extension (by adding -- --
-- {-# LANGUAGE PostfixOperators #-}
--
--
-- to the top of your file) or use seconds in prefix form:
--
-- -- 5.5 seconds --seconds :: Rational -> Int -- | Launch an external application through the system shell and return a -- Handle to its standard input. spawnPipe :: MonadIO m => String -> m Handle -- | Computation hPutStr hdl s writes the string s -- to the file or channel managed by hdl. -- -- This operation may fail with: -- --
-- $ darcs get <http://gorgias.mine.nu/repos/xmonad-utils> --module XMonad.Util.XSelection -- | Returns a String corresponding to the current mouse selection in X; if -- there is none, an empty string is returned. -- -- WARNING: this function is fundamentally implemented incorrectly and -- may, among other possible failure modes, deadlock or crash. For -- details, see -- http://code.google.com/p/xmonad/issues/detail?id=573. (These -- errors are generally very rare in practice, but still exist.) getSelection :: MonadIO m => m String -- | A wrapper around getSelection. Makes it convenient to run a -- program with the current selection as an argument. This is convenient -- for handling URLs, in particular. For example, in your Config.hs you -- could bind a key to promptSelection "firefox"; this would -- allow you to highlight a URL string and then immediately open it up in -- Firefox. -- -- promptSelection passes strings through the system shell, -- /bin/sh; if you do not wish your selected text to be interpreted or -- mangled by the shell, use safePromptSelection. -- safePromptSelection will bypass the shell using safeSpawn from -- XMonad.Util.Run; see its documentation for more details on the -- advantages and disadvantages of using safeSpawn. promptSelection :: String -> X () -- | A wrapper around getSelection. Makes it convenient to run a -- program with the current selection as an argument. This is convenient -- for handling URLs, in particular. For example, in your Config.hs you -- could bind a key to promptSelection "firefox"; this would -- allow you to highlight a URL string and then immediately open it up in -- Firefox. -- -- promptSelection passes strings through the system shell, -- /bin/sh; if you do not wish your selected text to be interpreted or -- mangled by the shell, use safePromptSelection. -- safePromptSelection will bypass the shell using safeSpawn from -- XMonad.Util.Run; see its documentation for more details on the -- advantages and disadvantages of using safeSpawn. safePromptSelection :: String -> X () -- | A wrapper around promptSelection and its safe variant. They -- take two parameters, the first is a function that transforms strings, -- and the second is the application to run. The transformer essentially -- transforms the selection in X. One example is to wrap code, such as a -- command line action copied out of the browser to be run as "sudo" -- ++ cmd or "su - -c ""++ cmd ++""". transformPromptSelection :: (String -> String) -> String -> X () -- | A wrapper around promptSelection and its safe variant. They -- take two parameters, the first is a function that transforms strings, -- and the second is the application to run. The transformer essentially -- transforms the selection in X. One example is to wrap code, such as a -- command line action copied out of the browser to be run as "sudo" -- ++ cmd or "su - -c ""++ cmd ++""". transformSafePromptSelection :: (String -> String) -> String -> X () -- | A module for sending key presses to windows. This modules provides -- generalized and specialized functions for this task. module XMonad.Util.Paste -- | Paste the current X mouse selection. Note that this uses -- getSelection from XMonad.Util.XSelection and so is heir -- to its flaws. pasteSelection :: X () -- | Send a string to the window which is currently focused. This function -- correctly handles capitalization. Warning: in dealing with capitalized -- characters, this assumes a QWERTY layout. pasteString :: String -> X () -- | Send a character to the current window. This is more low-level. -- Remember that you must handle the case of capitalization -- appropriately. That is, from the window's perspective: -- --
-- pasteChar mod2Mask 'F' ~> "f" ---- -- You would want to do something like: -- --
-- pasteChar shiftMask 'F' ---- -- Note that this function makes use of stringToKeysym, and so -- will probably have trouble with any Char outside ASCII. pasteChar :: KeyMask -> Char -> X () sendKey :: KeyMask -> KeySym -> X () -- | The primitive. Allows you to send any combination of KeyMask -- and KeySym to any Window you specify. sendKeyWindow :: KeyMask -> KeySym -> Window -> X () noModMask :: KeyMask -- | An example external contrib module for XMonad. Provides a simple -- binding to dzen2 to print the date as a popup menu. module XMonad.Actions.SimpleDate date :: X () -- | Handy wrapper for dzen. Requires dzen >= 0.2.4. module XMonad.Util.Dzen -- | dzenConfig config s will display the string s -- according to the configuration config. For example, to -- display the string "foobar" with all the default settings, -- you can simply call -- --
-- dzenConfig return "foobar" ---- -- Or, to set a longer timeout, you could use -- --
-- dzenConfig (timeout 10) "foobar" ---- -- You can combine configurations with the (>=>) operator. To -- display "foobar" for 10 seconds on the first screen, you -- could use -- --
-- dzenConfig (timeout 10 >=> xScreen 0) "foobar" ---- -- As a final example, you could adapt the above to display -- "foobar" for 10 seconds on the current screen with -- --
-- dzenConfig (timeout 10 >=> onCurr xScreen) "foobar" --dzenConfig :: DzenConfig -> String -> X () type DzenConfig = (Int, [String]) -> X (Int, [String]) -- | Set the timeout, in seconds. This defaults to 3 seconds if not -- specified. timeout :: Rational -> DzenConfig -- | Specify the font. Check out xfontsel to get the format of the String -- right; if your dzen supports xft, then you can supply that here, too. font :: String -> DzenConfig -- | Start dzen2 on a particular screen. Only works with versions of dzen -- that support the "-xs" argument. xScreen :: ScreenId -> DzenConfig -- | vCenter height sc sets the configuration to have the dzen bar -- appear on screen sc with height height, vertically -- centered with respect to the actual size of that screen. vCenter :: Int -> ScreenId -> DzenConfig -- | hCenter width sc sets the configuration to have the dzen bar -- appear on screen sc with width width, horizontally -- centered with respect to the actual size of that screen. hCenter :: Int -> ScreenId -> DzenConfig -- | center width height sc sets the configuration to have the -- dzen bar appear on screen sc with width width and -- height height, centered both horizontally and vertically with -- respect to the actual size of that screen. center :: Int -> Int -> ScreenId -> DzenConfig -- | Take a screen-specific configuration and supply it with the screen ID -- of the currently focused screen, according to xmonad. For example, -- show a 100-pixel wide bar centered within the current screen, you -- could use -- --
-- dzenConfig (onCurr (hCenter 100)) "foobar" ---- -- Of course, you can still combine these with (>=>); for example, -- to center the string "foobar" both horizontally and -- vertically in a 100x14 box using the lovely Terminus font, you could -- use -- --
-- terminus = "-*-terminus-*-*-*-*-12-*-*-*-*-*-*-*" -- dzenConfig (onCurr (center 100 14) >=> font terminus) "foobar" --onCurr :: (ScreenId -> DzenConfig) -> DzenConfig -- | Put the top of the dzen bar at a particular pixel. x :: Int -> DzenConfig -- | Put the left of the dzen bar at a particular pixel. y :: Int -> DzenConfig -- | Add raw command-line arguments to the configuration. These will be -- passed on verbatim to dzen2. The default includes no arguments. addArgs :: [String] -> DzenConfig -- | dzen str timeout pipes str to dzen2 for -- timeout microseconds. Example usage: -- --
-- dzen "Hi, mom!" (5 `seconds`) --dzen :: String -> Int -> X () -- | dzenScreen sc str timeout pipes str to dzen2 for -- timeout microseconds, and on screen sc. Requires -- dzen to be compiled with Xinerama support. dzenScreen :: ScreenId -> String -> Int -> X () -- | dzen str args timeout pipes str to dzen2 for -- timeout seconds, passing args to dzen. Example -- usage: -- --
-- dzenWithArgs "Hi, dons!" ["-ta", "r"] (5 `seconds`) --dzenWithArgs :: String -> [String] -> Int -> X () -- | Multiplies by ONE MILLION, for functions that take microseconds. -- -- Use like: -- --
-- (5.5 `seconds`) ---- -- In GHC 7 and later, you must either enable the PostfixOperators -- extension (by adding -- --
-- {-# LANGUAGE PostfixOperators #-}
--
--
-- to the top of your file) or use seconds in prefix form:
--
-- -- 5.5 seconds --seconds :: Rational -> Int -- | dzen wants exactly one newline at the end of its input, so this can be -- used for your own invocations of dzen. However, all functions in this -- module will call this for you. chomp :: String -> String -- | Left-to-right Kleisli composition of monads. (>=>) :: Monad m => (a -> m b) -> (b -> m c) -> a -> m c -- | This module allows you to associate the X titles of windows with them. module XMonad.Util.NamedWindows data NamedWindow getName :: Window -> X NamedWindow withNamedWindow :: (NamedWindow -> X ()) -> X () unName :: NamedWindow -> Window instance GHC.Classes.Eq XMonad.Util.NamedWindows.NamedWindow instance GHC.Classes.Ord XMonad.Util.NamedWindows.NamedWindow instance GHC.Show.Show XMonad.Util.NamedWindows.NamedWindow -- | A module for abstracting a font facility over Core fonts and Xft module XMonad.Util.Font data XMonadFont Core :: FontStruct -> XMonadFont Utf8 :: FontSet -> XMonadFont Xft :: XftFont -> XMonadFont -- | When initXMF gets a font name that starts with 'xft:' it switches to -- the Xft backend Example: 'xft: Sans-10' initXMF :: String -> X XMonadFont releaseXMF :: XMonadFont -> X () -- | Given a fontname returns the font structure. If the font name is not -- valid the default font will be loaded and returned. initCoreFont :: String -> X FontStruct releaseCoreFont :: FontStruct -> X () initUtf8Font :: String -> X FontSet releaseUtf8Font :: FontSet -> X () -- | String position data Align AlignCenter :: Align AlignRight :: Align AlignLeft :: Align AlignRightOffset :: Int -> Align -- | Return the string x and y Position in a Rectangle, given -- a FontStruct and the Alignment stringPosition :: (Functor m, MonadIO m) => Display -> XMonadFont -> Rectangle -> Align -> String -> m (Position, Position) textWidthXMF :: MonadIO m => Display -> XMonadFont -> String -> m Int textExtentsXMF :: MonadIO m => XMonadFont -> String -> m (Int32, Int32) printStringXMF :: (Functor m, MonadIO m) => Display -> Drawable -> XMonadFont -> GC -> String -> String -> Position -> Position -> String -> m () -- | Get the Pixel value for a named color: if an invalid name is given the -- black pixel will be returned. stringToPixel :: (Functor m, MonadIO m) => Display -> String -> m Pixel -- | Short-hand for fromIntegral fi :: (Integral a, Num b) => a -> b instance GHC.Read.Read XMonad.Util.Font.Align instance GHC.Show.Show XMonad.Util.Font.Align -- | Utilities for manipulating [[Bool]] as images module XMonad.Util.Image -- | Placement of the icon in the title bar data Placement -- | An exact amount of pixels from the upper left corner OffsetLeft :: Int -> Int -> Placement -- | An exact amount of pixels from the right left corner OffsetRight :: Int -> Int -> Placement -- | Centered in the y-axis, an amount of pixels from the left CenterLeft :: Int -> Placement -- | Centered in the y-axis, an amount of pixels from the right CenterRight :: Int -> Placement -- | Return the x and y positions inside a -- Rectangle to start drawing the image given its Placement iconPosition :: Rectangle -> Placement -> [[Bool]] -> (Position, Position) -- | Draw an image into a X surface drawIcon :: (Functor m, MonadIO m) => Display -> Drawable -> GC -> String -> String -> Position -> Position -> [[Bool]] -> m () instance GHC.Read.Read XMonad.Util.Image.Placement instance GHC.Show.Show XMonad.Util.Image.Placement -- | Add a configurable amount of space around windows. module XMonad.Layout.Spacing -- | Surround all windows by a certain number of pixels of blank space. spacing :: Int -> l a -> ModifiedLayout Spacing l a data Spacing a -- | Surround all windows by a certain number of pixels of blank space, and -- additionally adds the same amount of spacing around the edge of the -- screen. spacingWithEdge :: Int -> l a -> ModifiedLayout SpacingWithEdge l a data SpacingWithEdge a -- | Surrounds all windows with blank space, except when the window is the -- only visible window on the current workspace. smartSpacing :: Int -> l a -> ModifiedLayout SmartSpacing l a data SmartSpacing a -- | Surrounds all windows with blank space, and adds the same amount of -- spacing around the edge of the screen, except when the window is the -- only visible window on the current workspace. smartSpacingWithEdge :: Int -> l a -> ModifiedLayout SmartSpacingWithEdge l a data SmartSpacingWithEdge a -- | Message to dynamically modify (e.g. increasedecreaseset) the -- size of the window spacing data ModifySpacing ModifySpacing :: (Int -> Int) -> ModifySpacing -- | Set spacing to given amount setSpacing :: Int -> X () -- | Increase spacing by given amount incSpacing :: Int -> X () instance GHC.Read.Read (XMonad.Layout.Spacing.SmartSpacingWithEdge a) instance GHC.Show.Show (XMonad.Layout.Spacing.SmartSpacingWithEdge a) instance GHC.Read.Read (XMonad.Layout.Spacing.SmartSpacing a) instance GHC.Show.Show (XMonad.Layout.Spacing.SmartSpacing a) instance GHC.Read.Read (XMonad.Layout.Spacing.SpacingWithEdge a) instance GHC.Show.Show (XMonad.Layout.Spacing.SpacingWithEdge a) instance GHC.Read.Read (XMonad.Layout.Spacing.Spacing a) instance GHC.Show.Show (XMonad.Layout.Spacing.Spacing a) instance XMonad.Core.Message XMonad.Layout.Spacing.ModifySpacing instance XMonad.Layout.LayoutModifier.LayoutModifier XMonad.Layout.Spacing.Spacing a instance XMonad.Layout.LayoutModifier.LayoutModifier XMonad.Layout.Spacing.SpacingWithEdge a instance XMonad.Layout.LayoutModifier.LayoutModifier XMonad.Layout.Spacing.SmartSpacing a instance XMonad.Layout.LayoutModifier.LayoutModifier XMonad.Layout.Spacing.SmartSpacingWithEdge a -- | Focus the nth window of the current workspace. module XMonad.Actions.FocusNth -- | Give focus to the nth window of the current workspace. focusNth :: Int -> X () focusNth' :: Int -> Stack a -> Stack a -- | Like XMonad.Actions.Plane for an arbitrary number of -- dimensions. module XMonad.Actions.WorkspaceCursors focusDepth :: Cursors t -> Int -- | makeCursors requires a nonempty string, and each sublist must be -- nonempty makeCursors :: [[String]] -> Cursors String -- | List of elements of a structure, from left to right. toList :: Foldable t => forall a. t a -> [a] -- | The state is stored in the WorkspaceCursors layout modifier. -- Put this as your outermost modifier, unless you want different cursors -- at different times (using XMonad.Layout.MultiToggle) workspaceCursors :: Cursors String -> l a -> ModifiedLayout WorkspaceCursors l a data WorkspaceCursors a getFocus :: Cursors b -> b -- | modifyLayer is used to change the focus at a given depth modifyLayer :: (Stack (Cursors String) -> Stack (Cursors String)) -> Int -> X () -- | example usages are shiftLayer and shiftModifyLayer modifyLayer' :: (Stack (Cursors String) -> X (Stack (Cursors String))) -> Int -> X () -- | shiftModifyLayer is the same as modifyLayer, but also -- shifts the currently focused window to the new workspace shiftModifyLayer :: (Stack (Cursors String) -> Stack (Cursors WorkspaceId)) -> Int -> X () -- | shiftLayer is the same as shiftModifyLayer, but the -- focus remains on the current workspace. shiftLayer :: (Stack (Cursors String) -> Stack (Cursors WorkspaceId)) -> Int -> X () focusNth' :: Int -> Stack a -> Stack a -- | non-wrapping version of focusUp' noWrapUp :: Stack t -> Stack t -- | non-wrapping version of focusDown' noWrapDown :: Stack t -> Stack t data Cursors a instance GHC.Show.Show (XMonad.Actions.WorkspaceCursors.WorkspaceCursors a) instance GHC.Read.Read (XMonad.Actions.WorkspaceCursors.WorkspaceCursors a) instance GHC.Read.Read a => GHC.Read.Read (XMonad.Actions.WorkspaceCursors.Cursors a) instance GHC.Show.Show a => GHC.Show.Show (XMonad.Actions.WorkspaceCursors.Cursors a) instance GHC.Classes.Eq a => GHC.Classes.Eq (XMonad.Actions.WorkspaceCursors.Cursors a) instance Data.Foldable.Foldable XMonad.Actions.WorkspaceCursors.Cursors instance GHC.Base.Functor XMonad.Actions.WorkspaceCursors.Cursors instance XMonad.Core.Message XMonad.Actions.WorkspaceCursors.ChangeCursors instance XMonad.Layout.LayoutModifier.LayoutModifier XMonad.Actions.WorkspaceCursors.WorkspaceCursors a -- | Move and resize floating windows. module XMonad.Actions.FloatKeys -- | keysMoveWindow (dx, dy) moves the window by dx -- pixels to the right and dy pixels down. keysMoveWindow :: D -> Window -> X () -- | keysMoveWindowTo (x, y) (gx, gy) moves the window relative -- point (gx, gy) to the point (x,y), where -- (gx,gy) gives a position relative to the window border, i.e. -- gx = 0 is the left border, gx = 1 is the right -- border, gy = 0 is the top border, and gy = 1 the -- bottom border. -- -- For example, on a 1024x768 screen: -- --
-- keysMoveWindowTo (512,384) (1%2, 1%2) -- center the window on screen -- keysMoveWindowTo (1024,0) (1, 0) -- put window in the top right corner --keysMoveWindowTo :: P -> G -> Window -> X () -- | keysResizeWindow (dx, dy) (gx, gy) changes the width by -- dx and the height by dy, leaving the window-relative -- point (gx, gy) fixed. -- -- For example: -- --
-- keysResizeWindow (10, 0) (0, 0) -- make the window 10 pixels larger to the right -- keysResizeWindow (10, 0) (0, 1%2) -- does the same, unless sizeHints are applied -- keysResizeWindow (10, 10) (1%2, 1%2) -- add 5 pixels on each side -- keysResizeWindow (-10, -10) (0, 1) -- shrink the window in direction of the bottom-left corner --keysResizeWindow :: D -> G -> Window -> X () -- | keysAbsResizeWindow (dx, dy) (ax, ay) changes the width by -- dx and the height by dy, leaving the screen absolute -- point (ax, ay) fixed. -- -- For example: -- --
-- keysAbsResizeWindow (10, 10) (0, 0) -- enlarge the window; if it is not in the top-left corner it will also be moved down and to the right. --keysAbsResizeWindow :: D -> D -> Window -> X () type P = (Position, Position) type G = (Rational, Rational) -- | A module for painting on the screen module XMonad.Util.XUtils -- | Compute the weighted average the colors of two given Pixel values. averagePixels :: Pixel -> Pixel -> Double -> X Pixel -- | Create a simple window given a rectangle. If Nothing is given only the -- exposureMask will be set, otherwise the Just value. Use -- showWindow to map and hideWindow to unmap. createNewWindow :: Rectangle -> Maybe EventMask -> String -> Bool -> X Window -- | Map a window showWindow :: Window -> X () -- | the list version showWindows :: [Window] -> X () -- | unmap a window hideWindow :: Window -> X () -- | the list version hideWindows :: [Window] -> X () -- | destroy a window deleteWindow :: Window -> X () -- | the list version deleteWindows :: [Window] -> X () -- | Fill a window with a rectangle and a border paintWindow :: Window -> Dimension -> Dimension -> Dimension -> String -> String -> X () -- | Fill a window with a rectangle and a border, and write | a number of -- strings to given positions paintAndWrite :: Window -> XMonadFont -> Dimension -> Dimension -> Dimension -> String -> String -> String -> String -> [Align] -> [String] -> X () -- | Fill a window with a rectangle and a border, and write | a number of -- strings and a number of icons to given positions paintTextAndIcons :: Window -> XMonadFont -> Dimension -> Dimension -> Dimension -> String -> String -> String -> String -> [Align] -> [String] -> [Placement] -> [[[Bool]]] -> X () -- | Get the Pixel value for a named color: if an invalid name is given the -- black pixel will be returned. stringToPixel :: (Functor m, MonadIO m) => Display -> String -> m Pixel -- | Short-hand for fromIntegral fi :: (Integral a, Num b) => a -> b -- | This is a pure layout modifier that will let you move and resize -- windows with the keyboard in any layout. module XMonad.Layout.WindowArranger -- | A layout modifier to float the windows in a workspace windowArrange :: l a -> ModifiedLayout WindowArranger l a -- | A layout modifier to float all the windows in a workspace windowArrangeAll :: l a -> ModifiedLayout WindowArranger l a data WindowArrangerMsg DeArrange :: WindowArrangerMsg Arrange :: WindowArrangerMsg IncreaseLeft :: Int -> WindowArrangerMsg IncreaseRight :: Int -> WindowArrangerMsg IncreaseUp :: Int -> WindowArrangerMsg IncreaseDown :: Int -> WindowArrangerMsg DecreaseLeft :: Int -> WindowArrangerMsg DecreaseRight :: Int -> WindowArrangerMsg DecreaseUp :: Int -> WindowArrangerMsg DecreaseDown :: Int -> WindowArrangerMsg MoveLeft :: Int -> WindowArrangerMsg MoveRight :: Int -> WindowArrangerMsg MoveUp :: Int -> WindowArrangerMsg MoveDown :: Int -> WindowArrangerMsg SetGeometry :: Rectangle -> WindowArrangerMsg data WindowArranger a -- | Given a function to be applied to each member of ta list, and a -- function to check a condition by processing this transformed member -- with something, you get the first member that satisfy the condition, -- or an empty list. memberFromList :: (b -> c) -> (c -> a -> Bool) -> a -> [b] -> [b] -- | Given a function to be applied to each member of a list, and a -- function to check a condition by processing this transformed member -- with the members of a list, you get the list of members that satisfy -- the condition. listFromList :: (b -> c) -> (c -> [a] -> Bool) -> [a] -> [b] -> [b] -- | Get the list of elements to be deleted and the list of elements to be -- added to the first list in order to get the second list. diff :: Eq a => ([a], [a]) -> ([a], [a]) instance GHC.Show.Show a => GHC.Show.Show (XMonad.Layout.WindowArranger.WindowArranger a) instance GHC.Read.Read a => GHC.Read.Read (XMonad.Layout.WindowArranger.WindowArranger a) instance GHC.Show.Show a => GHC.Show.Show (XMonad.Layout.WindowArranger.ArrangedWindow a) instance GHC.Read.Read a => GHC.Read.Read (XMonad.Layout.WindowArranger.ArrangedWindow a) instance XMonad.Core.Message XMonad.Layout.WindowArranger.WindowArrangerMsg instance (GHC.Show.Show a, GHC.Read.Read a, GHC.Classes.Eq a) => XMonad.Layout.LayoutModifier.LayoutModifier XMonad.Layout.WindowArranger.WindowArranger a -- | Causes the pointer to follow whichever window focus changes to. -- Compliments the idea of switching focus as the mouse crosses window -- boundaries to keep the mouse near the currently focused window module XMonad.Actions.UpdatePointer -- | Update the pointer's location to the currently focused window or empty -- screen unless it's already there, or unless the user was changing -- focus with the mouse updatePointer :: (Rational, Rational) -> (Rational, Rational) -> X () -- | Automagically put the focused window in the master area. module XMonad.Layout.MagicFocus -- | Create a new layout which automagically puts the focused window in the -- master area. magicFocus :: l a -> ModifiedLayout MagicFocus l a -- | An eventHook that overrides the normal focusFollowsMouse. When the -- mouse it moved to another window, that window is replaced as the -- master, and the mouse is warped to inside the new master. -- -- It prevents infinite loops when focusFollowsMouse is true (the -- default), and MagicFocus is in use when changing focus with the mouse. -- -- This eventHook does nothing when there are floating windows on the -- current workspace. promoteWarp :: Event -> X All -- | promoteWarp' allows you to specify an arbitrary pair of arguments to -- pass to updatePointer when the mouse enters another window. promoteWarp' :: (Rational, Rational) -> (Rational, Rational) -> Event -> X All -- | Another event hook to override the focusFollowsMouse and make the -- pointer only follow if a given condition is satisfied. This could be -- used to disable focusFollowsMouse only for given workspaces or -- layouts. Beware that your focusFollowsMouse setting is ignored if you -- use this event hook. followOnlyIf :: X Bool -> Event -> X All -- | Disables focusFollow on the given workspaces: disableFollowOnWS :: [WorkspaceId] -> X Bool data MagicFocus a instance GHC.Read.Read (XMonad.Layout.MagicFocus.MagicFocus a) instance GHC.Show.Show (XMonad.Layout.MagicFocus.MagicFocus a) instance XMonad.Layout.LayoutModifier.LayoutModifier XMonad.Layout.MagicFocus.MagicFocus Graphics.X11.Types.Window -- | Screenshot : http://caladan.rave.org/magnifier.png -- -- This is a layout modifier that will make a layout increase the size of -- the window that has focus. module XMonad.Layout.Magnifier -- | Increase the size of the window that has focus magnifier :: l a -> ModifiedLayout Magnifier l a -- | Increase the size of the window that has focus, unless if it is the -- master window. magnifier' :: l a -> ModifiedLayout Magnifier l a -- | Magnifier that defaults to Off magnifierOff :: l a -> ModifiedLayout Magnifier l a -- | Change the size of the window that has focus by a custom zoom magnifiercz :: Rational -> l a -> ModifiedLayout Magnifier l a -- | Increase the size of the window that has focus by a custom zoom, -- unless if it is the master window. magnifiercz' :: Rational -> l a -> ModifiedLayout Magnifier l a -- | A magnifier that greatly magnifies just the vertical direction maximizeVertical :: l a -> ModifiedLayout Magnifier l a data MagnifyMsg MagnifyMore :: MagnifyMsg MagnifyLess :: MagnifyMsg ToggleOn :: MagnifyMsg ToggleOff :: MagnifyMsg Toggle :: MagnifyMsg data Magnifier a instance GHC.Show.Show (XMonad.Layout.Magnifier.Magnifier a) instance GHC.Read.Read (XMonad.Layout.Magnifier.Magnifier a) instance GHC.Show.Show XMonad.Layout.Magnifier.MagnifyMaster instance GHC.Read.Read XMonad.Layout.Magnifier.MagnifyMaster instance GHC.Show.Show XMonad.Layout.Magnifier.Toggle instance GHC.Read.Read XMonad.Layout.Magnifier.Toggle instance XMonad.Core.Message XMonad.Layout.Magnifier.MagnifyMsg instance XMonad.Layout.LayoutModifier.LayoutModifier XMonad.Layout.Magnifier.Magnifier Graphics.X11.Types.Window -- | A layout in the spirit of XMonad.Layout.ResizableTile, but with -- the option to use the mouse to adjust the layout. module XMonad.Layout.MouseResizableTile mouseResizableTile :: MouseResizableTile a -- | May be removed in favor of mouseResizableTile { isMirrored = True -- } mouseResizableTileMirrored :: MouseResizableTile a data MRTMessage ShrinkSlave :: MRTMessage ExpandSlave :: MRTMessage -- | Get/set the number of windows in master pane (default: 1). nmaster :: MouseResizableTile a -> Int -- | Get/set the proportion of screen occupied by master pane (default: -- 1/2). masterFrac :: MouseResizableTile a -> Rational -- | Get/set the proportion of remaining space in a column occupied by a -- slave window (default: 1/2). slaveFrac :: MouseResizableTile a -> Rational -- | Get/set the increment used when modifying masterFrac/slaveFrac by the -- Shrink, Expand, etc. messages (default: 3/100). fracIncrement :: MouseResizableTile a -> Rational -- | Get/set whether the layout is mirrored (default: False). isMirrored :: MouseResizableTile a -> Bool -- | Get/set dragger and gap dimensions (default: FixedDragger 6 6). draggerType :: MouseResizableTile a -> DraggerType -- | Specifies the size of the clickable area between windows. data DraggerType FixedDragger :: Dimension -> Dimension -> DraggerType -- | width of a gap between windows [gapWidth] :: DraggerType -> Dimension -- | width of the dragger itself (will overlap windows if greater than gap) [draggerWidth] :: DraggerType -> Dimension -- | no gaps, draggers overlap window borders BordersDragger :: DraggerType data MouseResizableTile a instance GHC.Read.Read (XMonad.Layout.MouseResizableTile.MouseResizableTile a) instance GHC.Show.Show (XMonad.Layout.MouseResizableTile.MouseResizableTile a) instance GHC.Read.Read XMonad.Layout.MouseResizableTile.DraggerType instance GHC.Show.Show XMonad.Layout.MouseResizableTile.DraggerType instance GHC.Read.Read XMonad.Layout.MouseResizableTile.DraggerInfo instance GHC.Show.Show XMonad.Layout.MouseResizableTile.DraggerInfo instance XMonad.Core.Message XMonad.Layout.MouseResizableTile.MRTMessage instance XMonad.Core.LayoutClass XMonad.Layout.MouseResizableTile.MouseResizableTile Graphics.X11.Types.Window -- | Useful in a dual-head setup: Looks at the requested geometry of new -- windows and moves them to the workspace of the non-focused screen if -- necessary. module XMonad.Hooks.WorkspaceByPos workspaceByPos :: ManageHook -- | This is a layout modifier that will show the workspace name module XMonad.Layout.ShowWName -- | A layout modifier to show the workspace name when switching showWName :: l a -> ModifiedLayout ShowWName l a -- | A layout modifier to show the workspace name when switching. It is -- possible to provide a custom configuration. showWName' :: SWNConfig -> l a -> ModifiedLayout ShowWName l a -- | The default value for this type. def :: Default a => a -- | Deprecated: Use def (from Data.Default, and re-exported from -- XMonad.Layout.ShowWName) instead. defaultSWNConfig :: SWNConfig data SWNConfig SWNC :: String -> String -> String -> Rational -> SWNConfig -- | Font name [swn_font] :: SWNConfig -> String -- | Background color [swn_bgcolor] :: SWNConfig -> String -- | String color [swn_color] :: SWNConfig -> String -- | Time in seconds of the name visibility [swn_fade] :: SWNConfig -> Rational data ShowWName a instance GHC.Show.Show (XMonad.Layout.ShowWName.ShowWName a) instance GHC.Read.Read (XMonad.Layout.ShowWName.ShowWName a) instance GHC.Show.Show XMonad.Layout.ShowWName.SWNConfig instance GHC.Read.Read XMonad.Layout.ShowWName.SWNConfig instance Data.Default.Class.Default XMonad.Layout.ShowWName.SWNConfig instance XMonad.Layout.LayoutModifier.LayoutModifier XMonad.Layout.ShowWName.ShowWName a -- | Automatic placement of floating windows. module XMonad.Hooks.Place -- | Repositions the focused window according to a placement policy. Works -- for both "real" floating windows and windows in a -- WindowArranger-based layout. placeFocused :: Placement -> X () -- | Hook to automatically place windows when they are created. placeHook :: Placement -> ManageHook -- | The type of placement policies data Placement -- | Try to place windows with as little overlap as possible smart :: (Rational, Rational) -> Placement simpleSmart :: Placement -- | Place windows at a fixed position fixed :: (Rational, Rational) -> Placement -- | Place windows under the mouse underMouse :: (Rational, Rational) -> Placement -- | Apply the given placement policy, constraining the placed windows -- inside the screen boundaries. inBounds :: Placement -> Placement -- | Same as inBounds, but allows specifying gaps along the screen's -- edges withGaps :: (Dimension, Dimension, Dimension, Dimension) -> Placement -> Placement -- | Compute the new position of a window according to a placement policy. purePlaceWindow :: Placement -> Rectangle -> [Rectangle] -> (Position, Position) -> Rectangle -> Rectangle instance GHC.Classes.Eq a => GHC.Classes.Eq (XMonad.Hooks.Place.SmartRectangle a) instance GHC.Show.Show a => GHC.Show.Show (XMonad.Hooks.Place.SmartRectangle a) instance GHC.Classes.Eq XMonad.Hooks.Place.Placement instance GHC.Read.Read XMonad.Hooks.Place.Placement instance GHC.Show.Show XMonad.Hooks.Place.Placement -- | Layouts that splits the screen either horizontally or vertically and -- shows two windows. The first window is always the master window, and -- the other is either the currently focused window or the second window -- in layout order. module XMonad.Layout.DragPane dragPane :: DragType -> Double -> Double -> DragPane a data DragPane a data DragType Horizontal :: DragType Vertical :: DragType instance GHC.Classes.Eq XMonad.Layout.DragPane.SetFrac instance GHC.Read.Read XMonad.Layout.DragPane.SetFrac instance GHC.Show.Show XMonad.Layout.DragPane.SetFrac instance GHC.Read.Read (XMonad.Layout.DragPane.DragPane a) instance GHC.Show.Show (XMonad.Layout.DragPane.DragPane a) instance GHC.Read.Read XMonad.Layout.DragPane.DragType instance GHC.Show.Show XMonad.Layout.DragPane.DragType instance XMonad.Core.LayoutClass XMonad.Layout.DragPane.DragPane a instance XMonad.Core.Message XMonad.Layout.DragPane.SetFrac -- | Reflect a layout horizontally or vertically. module XMonad.Layout.Reflect -- | Apply a horizontal reflection (left <--> right) to a layout. reflectHoriz :: l a -> ModifiedLayout Reflect l a -- | Apply a vertical reflection (top <--> bottom) to a layout. reflectVert :: l a -> ModifiedLayout Reflect l a data REFLECTX REFLECTX :: REFLECTX data REFLECTY REFLECTY :: REFLECTY data Reflect a instance GHC.Classes.Eq XMonad.Layout.Reflect.REFLECTY instance GHC.Show.Show XMonad.Layout.Reflect.REFLECTY instance GHC.Read.Read XMonad.Layout.Reflect.REFLECTY instance GHC.Classes.Eq XMonad.Layout.Reflect.REFLECTX instance GHC.Show.Show XMonad.Layout.Reflect.REFLECTX instance GHC.Read.Read XMonad.Layout.Reflect.REFLECTX instance GHC.Read.Read (XMonad.Layout.Reflect.Reflect a) instance GHC.Show.Show (XMonad.Layout.Reflect.Reflect a) instance GHC.Show.Show XMonad.Layout.Reflect.ReflectDir instance GHC.Read.Read XMonad.Layout.Reflect.ReflectDir instance XMonad.Layout.LayoutModifier.LayoutModifier XMonad.Layout.Reflect.Reflect a instance XMonad.Layout.MultiToggle.Transformer XMonad.Layout.Reflect.REFLECTX Graphics.X11.Types.Window instance XMonad.Layout.MultiToggle.Transformer XMonad.Layout.Reflect.REFLECTY Graphics.X11.Types.Window -- | A layout modifier that puts some windows in a "drawer" which retracts -- and expands depending on whether any window in it has focus. -- -- Useful for music players, tool palettes, etc. module XMonad.Layout.Drawer -- | Construct a drawer with a simple layout of the windows inside simpleDrawer :: Rational -> Rational -> Property -> Drawer Tall a -- | Construct a drawer with an arbitrary layout for windows inside drawer :: Rational -> Rational -> Property -> (l a) -> Drawer l a onLeft :: Drawer l a -> l' a -> ModifiedLayout (Drawer l) l' a onTop :: Drawer l a -> l' a -> Mirror (ModifiedLayout (Drawer l) (Mirror l')) a onRight :: Drawer l a -> l' a -> Reflected (ModifiedLayout (Drawer l) (Reflected l')) a onBottom :: Drawer l a -> l' a -> Reflected (Mirror (ModifiedLayout (Drawer l) (Mirror (Reflected l')))) a data Drawer l a type Reflected l = ModifiedLayout Reflect l instance GHC.Show.Show (l a) => GHC.Show.Show (XMonad.Layout.Drawer.Drawer l a) instance GHC.Read.Read (l a) => GHC.Read.Read (XMonad.Layout.Drawer.Drawer l a) instance (XMonad.Core.LayoutClass l Graphics.X11.Types.Window, GHC.Read.Read (l Graphics.X11.Types.Window)) => XMonad.Layout.LayoutModifier.LayoutModifier (XMonad.Layout.Drawer.Drawer l) Graphics.X11.Types.Window -- | A basic floating layout like SimpleFloat but without the decoration. module XMonad.Layout.SimplestFloat -- | A simple floating layout where every window is placed according to the -- window's initial attributes. simplestFloat :: Eq a => (ModifiedLayout WindowArranger SimplestFloat) a data SimplestFloat a instance GHC.Read.Read (XMonad.Layout.SimplestFloat.SimplestFloat a) instance GHC.Show.Show (XMonad.Layout.SimplestFloat.SimplestFloat a) instance XMonad.Core.LayoutClass XMonad.Layout.SimplestFloat.SimplestFloat Graphics.X11.Types.Window -- | Resize floating windows from any corner. module XMonad.Actions.FlexibleResize -- | Resize a floating window from whichever corner the mouse is closest -- to. mouseResizeWindow :: Window -> X () -- | Resize a floating window from whichever corner or edge the mouse is -- closest to. mouseResizeEdgeWindow :: Rational -> Window -> X () -- | Move and resize floating windows without warping the mouse. module XMonad.Actions.FlexibleManipulate -- | Given an interpolation function, implement an appropriate window -- manipulation action. mouseWindow :: (Double -> Double) -> Window -> X () -- | Manipulate the window based on discrete pick regions; the window is -- divided into regions by thirds along each axis. discrete :: Double -> Double -- | Scale/reposition the window by factors obtained from the mouse -- position by linear interpolation. Dragging precisely on a corner -- resizes that corner; dragging precisely in the middle moves the window -- without resizing; anything else is an interpolation between the two. linear :: Double -> Double -- | Only resize the window, based on the window quadrant the mouse is in. resize :: Double -> Double -- | Only reposition the window. position :: Double -> Double -- | Find an empty workspace. module XMonad.Actions.FindEmptyWorkspace -- | Find and view an empty workspace. Do nothing if all workspaces are in -- use. viewEmptyWorkspace :: X () -- | Tag current window to an empty workspace and view it. Do nothing if -- all workspaces are in use. tagToEmptyWorkspace :: X () -- | Send current window to an empty workspace. Do nothing if all -- workspaces are in use. sendToEmptyWorkspace :: X () -- | Module for storing custom mutable state in xmonad. module XMonad.Util.ExtensibleState -- | Add a value to the extensible state field. A previously stored value -- with the same type will be overwritten. (More precisely: A value whose -- string representation of its type is equal to the new one's) put :: ExtensionClass a => a -> X () -- | Apply a function to a stored value of the matching type or the initial -- value if there is none. modify :: ExtensionClass a => (a -> a) -> X () -- | Remove the value from the extensible state field that has the same -- type as the supplied argument remove :: ExtensionClass a => a -> X () -- | Try to retrieve a value of the requested type, return an initial value -- if there is no such value. get :: ExtensionClass a => X a gets :: ExtensionClass a => (a -> b) -> X b -- | Provides methods for cycling through groups of windows across -- workspaces, ignoring windows that do not belong to this group. A group -- consists of all windows matching a user-provided boolean query. -- -- Also provides a method for jumping back to the most recently used -- window in any given group. module XMonad.Actions.GroupNavigation -- | The direction in which to look for the next match data Direction -- | Forward from current window or workspace Forward :: Direction -- | Backward from current window or workspace Backward :: Direction -- | Backward in history History :: Direction -- | Focuses the next window that matches the given boolean query. Does -- nothing if there is no such window. This is the same as -- nextMatchOrDo with alternate action return (). nextMatch :: Direction -> Query Bool -> X () -- | Focuses the next window that matches the given boolean query. If there -- is no such window, perform the given action instead. nextMatchOrDo :: Direction -> Query Bool -> X () -> X () -- | Focuses the next window for which the given query produces the same -- result as the currently focused window. Does nothing if there is no -- focused window (i.e., the current workspace is empty). nextMatchWithThis :: Eq a => Direction -> Query a -> X () -- | Action that needs to be executed as a logHook to maintain the focus -- history of all windows as the WindowSet changes. historyHook :: X () instance GHC.Show.Show XMonad.Actions.GroupNavigation.HistoryDB instance GHC.Read.Read XMonad.Actions.GroupNavigation.HistoryDB instance XMonad.Core.ExtensionClass XMonad.Actions.GroupNavigation.HistoryDB -- | Remap Keybinding on the fly, e.g having Dvorak char, but everything -- with Control/Shift is left us Layout module XMonad.Actions.KeyRemap -- | Using this in the keybindings to set the actual Key Translation table setKeyRemap :: KeymapTable -> X () -- | Append the output of this function to your keybindings with ++ buildKeyRemapBindings :: [KeymapTable] -> [((KeyMask, KeySym), X ())] -- | Adding this to your startupHook, to select your default Key -- Translation table. You also must give it all the KeymapTables you are -- willing to use setDefaultKeyRemap :: KeymapTable -> [KeymapTable] -> X () data KeymapTable KeymapTable :: [((KeyMask, KeySym), (KeyMask, KeySym))] -> KeymapTable -- | The empty KeymapTable, does no translation emptyKeyRemap :: KeymapTable -- | The dvorak Programmers keymap, translates from us keybindings to -- dvorak programmers dvorakProgrammerKeyRemap :: KeymapTable instance GHC.Show.Show XMonad.Actions.KeyRemap.KeymapTable instance XMonad.Core.ExtensionClass XMonad.Actions.KeyRemap.KeymapTable -- | ShowText displays text for sometime on the screen similar to -- XMonad.Util.Dzen which offers more features (currently) module XMonad.Actions.ShowText -- | The default value for this type. def :: Default a => a -- | Deprecated: Use def (from Data.Default, and re-exported by -- XMonad.Actions.ShowText) instead. defaultSTConfig :: ShowTextConfig -- | Handles timer events that notify when a window should be removed handleTimerEvent :: Event -> X All -- | Shows a window in the center of the screen with the given text flashText :: ShowTextConfig -> Rational -> String -> X () data ShowTextConfig STC :: String -> String -> String -> ShowTextConfig -- | Font name [st_font] :: ShowTextConfig -> String -- | Background color [st_bg] :: ShowTextConfig -> String -- | Foreground color [st_fg] :: ShowTextConfig -> String instance GHC.Show.Show XMonad.Actions.ShowText.ShowText instance GHC.Read.Read XMonad.Actions.ShowText.ShowText instance XMonad.Core.ExtensionClass XMonad.Actions.ShowText.ShowText instance Data.Default.Class.Default XMonad.Actions.ShowText.ShowTextConfig -- | UrgencyHook lets you configure an action to occur when a window -- demands your attention. (In traditional WMs, this takes the form of -- "flashing" on your "taskbar." Blech.) module XMonad.Hooks.UrgencyHook -- | This is the method to enable an urgency hook. It uses the default -- urgencyConfig to control behavior. To change this, use -- withUrgencyHookC instead. withUrgencyHook :: (LayoutClass l Window, UrgencyHook h) => h -> XConfig l -> XConfig l -- | This lets you modify the defaults set in urgencyConfig. An -- example: -- --
-- withUrgencyHookC dzenUrgencyHook { ... } urgencyConfig { suppressWhen = Focused }
--
--
-- (Don't type the ..., you dolt.) See UrgencyConfig for
-- details on configuration.
withUrgencyHookC :: (LayoutClass l Window, UrgencyHook h) => h -> UrgencyConfig -> XConfig l -> XConfig l
-- | Global configuration, applied to all types of UrgencyHook. See
-- urgencyConfig for the defaults.
data UrgencyConfig
UrgencyConfig :: SuppressWhen -> RemindWhen -> UrgencyConfig
-- | when to trigger the urgency hook
[suppressWhen] :: UrgencyConfig -> SuppressWhen
-- | when to re-trigger the urgency hook
[remindWhen] :: UrgencyConfig -> RemindWhen
-- | The default UrgencyConfig. suppressWhen = Visible, remindWhen =
-- Dont. Use a variation of this in your config just as you use a
-- variation of def for your xmonad definition.
urgencyConfig :: UrgencyConfig
-- | A set of choices as to when you should (or rather, shouldn't)
-- be notified of an urgent window. The default is Visible. Prefix
-- each of the following with "don't bug me when":
data SuppressWhen
-- | the window is currently visible
Visible :: SuppressWhen
-- | the window is on the currently focused physical screen
OnScreen :: SuppressWhen
-- | the window is currently focused
Focused :: SuppressWhen
-- | ... aww, heck, go ahead and bug me, just in case.
Never :: SuppressWhen
-- | A set of choices as to when you want to be re-notified of an urgent
-- window. Perhaps you focused on something and you miss the dzen popup
-- bar. Or you're AFK. Or you feel the need to be more distracted. I
-- don't care.
--
-- The interval arguments are in seconds. See the minutes helper.
data RemindWhen
-- | triggering once is enough
Dont :: RemindWhen
-- | repeat arg1 times every arg2 seconds
Repeatedly :: Int -> Interval -> RemindWhen
-- | repeat every arg1 until the urgency hint is cleared
Every :: Interval -> RemindWhen
-- | Focuses the most recently urgent window. Good for what ails ya -- I
-- mean, your keybindings. Example keybinding:
--
-- -- , ((modm , xK_BackSpace), focusUrgent) --focusUrgent :: X () -- | Just makes the urgents go away. Example keybinding: -- --
-- , ((modm .|. shiftMask, xK_BackSpace), clearUrgents) --clearUrgents :: X () -- | Flashes when a window requests your attention and you can't see it. -- Defaults to a duration of five seconds, and no extra args to dzen. See -- DzenUrgencyHook. dzenUrgencyHook :: DzenUrgencyHook -- | Your set of options for configuring a dzenUrgencyHook. data DzenUrgencyHook DzenUrgencyHook :: Int -> [String] -> DzenUrgencyHook -- | number of microseconds to display the dzen (hence, you'll probably -- want to use seconds) [duration] :: DzenUrgencyHook -> Int -- | list of extra args (as Strings) to pass to dzen [args] :: DzenUrgencyHook -> [String] data NoUrgencyHook NoUrgencyHook :: NoUrgencyHook data BorderUrgencyHook BorderUrgencyHook :: !String -> BorderUrgencyHook [urgencyBorderColor] :: BorderUrgencyHook -> !String data FocusHook FocusHook :: FocusHook -- | urgencyhook such that windows on certain workspaces never get urgency -- set. -- -- Useful for scratchpad workspaces perhaps: -- --
-- main = xmonad (withUrgencyHook (filterUrgencyHook ["NSP", "SP"]) defaultConfig) --filterUrgencyHook :: [WorkspaceId] -> Window -> X () -- | A prettified way of multiplying by 60. Use like: (5 -- minutes). minutes :: Rational -> Rational -- | Multiplies by ONE MILLION, for functions that take microseconds. -- -- Use like: -- --
-- (5.5 `seconds`) ---- -- In GHC 7 and later, you must either enable the PostfixOperators -- extension (by adding -- --
-- {-# LANGUAGE PostfixOperators #-}
--
--
-- to the top of your file) or use seconds in prefix form:
--
-- -- 5.5 seconds --seconds :: Rational -> Int -- | X action that returns a list of currently urgent windows. You might -- use it, or withUrgents, in your custom logHook, to display the -- workspaces that contain urgent windows. readUrgents :: X [Window] -- | An HOF version of readUrgents, for those who prefer that sort -- of thing. withUrgents :: ([Window] -> X a) -> X a data StdoutUrgencyHook StdoutUrgencyHook :: StdoutUrgencyHook newtype SpawnUrgencyHook SpawnUrgencyHook :: String -> SpawnUrgencyHook -- | The class definition, and some pre-defined instances. class UrgencyHook h urgencyHook :: UrgencyHook h => h -> Window -> X () type Interval = Rational -- | A hook that sets the border color of an urgent window. The color will -- remain until the next time the window gains or loses focus, at which -- point the standard border color from the XConfig will be applied. You -- may want to use suppressWhen = Never with this: -- --
-- withUrgencyHookC BorderUrgencyHook { urgencyBorderColor = "#ff0000" } urgencyConfig { suppressWhen = Never } ...
--
--
-- (This should be urgentBorderColor but that breaks
-- XMonad.Layout.Decoration. borderColor breaks anyone
-- using XPConfig from XMonad.Prompt. We need to think a
-- bit more about namespacing issues, maybe.)
borderUrgencyHook :: String -> Window -> X ()
-- | A hook which will automatically send you to anything which sets the
-- urgent flag (as opposed to printing some sort of message. You would
-- use this as usual, eg.
--
--
-- withUrgencyHook FocusHook $ myconfig { ...
--
focusHook :: Window -> X ()
-- | Spawn a commandline thing, appending the window id to the prefix
-- string you provide. (Make sure to add a space if you need it.) Do your
-- crazy xcompmgr thing.
spawnUrgencyHook :: String -> Window -> X ()
-- | For debugging purposes, really.
stdoutUrgencyHook :: Window -> X ()
instance GHC.Show.Show XMonad.Hooks.UrgencyHook.StdoutUrgencyHook
instance GHC.Read.Read XMonad.Hooks.UrgencyHook.StdoutUrgencyHook
instance GHC.Show.Show XMonad.Hooks.UrgencyHook.SpawnUrgencyHook
instance GHC.Read.Read XMonad.Hooks.UrgencyHook.SpawnUrgencyHook
instance GHC.Show.Show XMonad.Hooks.UrgencyHook.BorderUrgencyHook
instance GHC.Read.Read XMonad.Hooks.UrgencyHook.BorderUrgencyHook
instance GHC.Show.Show XMonad.Hooks.UrgencyHook.FocusHook
instance GHC.Read.Read XMonad.Hooks.UrgencyHook.FocusHook
instance GHC.Show.Show XMonad.Hooks.UrgencyHook.DzenUrgencyHook
instance GHC.Read.Read XMonad.Hooks.UrgencyHook.DzenUrgencyHook
instance GHC.Show.Show XMonad.Hooks.UrgencyHook.NoUrgencyHook
instance GHC.Read.Read XMonad.Hooks.UrgencyHook.NoUrgencyHook
instance GHC.Show.Show h => GHC.Show.Show (XMonad.Hooks.UrgencyHook.WithUrgencyHook h)
instance GHC.Read.Read h => GHC.Read.Read (XMonad.Hooks.UrgencyHook.WithUrgencyHook h)
instance GHC.Classes.Eq XMonad.Hooks.UrgencyHook.Reminder
instance GHC.Read.Read XMonad.Hooks.UrgencyHook.Reminder
instance GHC.Show.Show XMonad.Hooks.UrgencyHook.Reminder
instance GHC.Show.Show XMonad.Hooks.UrgencyHook.UrgencyConfig
instance GHC.Read.Read XMonad.Hooks.UrgencyHook.UrgencyConfig
instance GHC.Show.Show XMonad.Hooks.UrgencyHook.RemindWhen
instance GHC.Read.Read XMonad.Hooks.UrgencyHook.RemindWhen
instance GHC.Show.Show XMonad.Hooks.UrgencyHook.SuppressWhen
instance GHC.Read.Read XMonad.Hooks.UrgencyHook.SuppressWhen
instance GHC.Show.Show XMonad.Hooks.UrgencyHook.Urgents
instance GHC.Read.Read XMonad.Hooks.UrgencyHook.Urgents
instance XMonad.Core.ExtensionClass XMonad.Hooks.UrgencyHook.Urgents
instance XMonad.Core.ExtensionClass [XMonad.Hooks.UrgencyHook.Reminder]
instance XMonad.Hooks.UrgencyHook.UrgencyHook (Graphics.X11.Types.Window -> XMonad.Core.X ())
instance XMonad.Hooks.UrgencyHook.UrgencyHook XMonad.Hooks.UrgencyHook.NoUrgencyHook
instance XMonad.Hooks.UrgencyHook.UrgencyHook XMonad.Hooks.UrgencyHook.DzenUrgencyHook
instance XMonad.Hooks.UrgencyHook.UrgencyHook XMonad.Hooks.UrgencyHook.FocusHook
instance XMonad.Hooks.UrgencyHook.UrgencyHook XMonad.Hooks.UrgencyHook.BorderUrgencyHook
instance XMonad.Hooks.UrgencyHook.UrgencyHook XMonad.Hooks.UrgencyHook.SpawnUrgencyHook
instance XMonad.Hooks.UrgencyHook.UrgencyHook XMonad.Hooks.UrgencyHook.StdoutUrgencyHook
-- | A layout modifier and a class for easily creating decorated layouts.
module XMonad.Layout.Decoration
-- | A layout modifier that, with a Shrinker, a Theme, a
-- DecorationStyle, and a layout, will decorate this layout
-- according to the decoration style provided.
--
-- For some usage examples see XMonad.Layout.DecorationMadness.
decoration :: (DecorationStyle ds a, Shrinker s) => s -> Theme -> ds a -> l a -> ModifiedLayout (Decoration ds s) l a
-- | A Theme is a record of colors, font etc., to customize a
-- DecorationStyle.
--
-- For a collection of Themes see XMonad.Util.Themes
data Theme
Theme :: String -> String -> String -> String -> String -> String -> String -> String -> String -> String -> Dimension -> Dimension -> [(String, Align)] -> [([[Bool]], Placement)] -> Theme
-- | Color of the active window
[activeColor] :: Theme -> String
-- | Color of the inactive window
[inactiveColor] :: Theme -> String
-- | Color of the urgent window
[urgentColor] :: Theme -> String
-- | Color of the border of the active window
[activeBorderColor] :: Theme -> String
-- | Color of the border of the inactive window
[inactiveBorderColor] :: Theme -> String
-- | Color of the border of the urgent window
[urgentBorderColor] :: Theme -> String
-- | Color of the text of the active window
[activeTextColor] :: Theme -> String
-- | Color of the text of the inactive window
[inactiveTextColor] :: Theme -> String
-- | Color of the text of the urgent window
[urgentTextColor] :: Theme -> String
-- | Font name
[fontName] :: Theme -> String
-- | Maximum width of the decorations (if supported by the
-- DecorationStyle)
[decoWidth] :: Theme -> Dimension
-- | Height of the decorations
[decoHeight] :: Theme -> Dimension
-- | Extra text to appear in a window's title bar. Refer to for a use
-- XMonad.Layout.ImageButtonDecoration
[windowTitleAddons] :: Theme -> [(String, Align)]
-- | Extra icons to appear in a window's title bar. Inner [Bool]
-- is a row in a icon bitmap.
[windowTitleIcons] :: Theme -> [([[Bool]], Placement)]
-- | The default xmonad Theme.
-- | Deprecated: Use def (from Data.Default, and re-exported by
-- XMonad.Layout.Decoration) instead.
defaultTheme :: Theme
-- | The default value for this type.
def :: Default a => a
-- | The Decoration LayoutModifier. This data type is an
-- instance of the LayoutModifier class. This data type will be
-- passed, together with a layout, to the ModifiedLayout type
-- constructor to modify the layout by adding decorations according to a
-- DecorationStyle.
data Decoration ds s a
-- | A Decoration layout modifier will handle SetTheme, a
-- message to dynamically change the decoration Theme.
data DecorationMsg
SetTheme :: Theme -> DecorationMsg
-- | The DecorationStyle class, defines methods used in the
-- implementation of the Decoration LayoutModifier
-- instance. A type instance of this class is passed to the
-- Decoration type in order to decorate a layout, by using these
-- methods.
class (Read (ds a), Show (ds a), Eq a) => DecorationStyle ds a where describeDeco ds = show ds shrink _ (Rectangle _ _ _ dh) (Rectangle x y w h) = Rectangle x (y + fi dh) w (h - dh) decorationEventHook ds s e = handleMouseFocusDrag ds s e decorationCatchClicksHook _ _ _ _ = return False decorationWhileDraggingHook _ ex ey (mainw, r) x y = handleDraggingInProgress ex ey (mainw, r) x y decorationAfterDraggingHook _ds (mainw, _r) _decoWin = focus mainw pureDecoration _ _ ht _ s _ (w, Rectangle x y wh ht') = if isInStack s w && (ht < ht') then Just $ Rectangle x y wh ht else Nothing decorate ds w h r s wrs wr = return $ pureDecoration ds w h r s wrs wr
-- | The description that the Decoration modifier will display.
describeDeco :: DecorationStyle ds a => ds a -> String
-- | Shrink the window's rectangle when applying a decoration.
shrink :: DecorationStyle ds a => ds a -> Rectangle -> Rectangle -> Rectangle
-- | The decoration event hook
decorationEventHook :: DecorationStyle ds a => ds a -> DecorationState -> Event -> X ()
-- | A hook that can be used to catch the cases when the user clicks on the
-- decoration. If you return True here, the click event will be
-- considered as dealt with and no further processing will take place.
decorationCatchClicksHook :: DecorationStyle ds a => ds a -> Window -> Int -> Int -> X Bool
-- | This hook is called while a window is dragged using the decoration.
-- The hook can be overwritten if a different way of handling the
-- dragging is required.
decorationWhileDraggingHook :: DecorationStyle ds a => ds a -> CInt -> CInt -> (Window, Rectangle) -> Position -> Position -> X ()
-- | This hoook is called after a window has been dragged using the
-- decoration.
decorationAfterDraggingHook :: DecorationStyle ds a => ds a -> (Window, Rectangle) -> Window -> X ()
-- | The pure version of the main method, decorate.
pureDecoration :: DecorationStyle ds a => ds a -> Dimension -> Dimension -> Rectangle -> Stack a -> [(a, Rectangle)] -> (a, Rectangle) -> Maybe Rectangle
-- | Given the theme's decoration width and height, the screen rectangle,
-- the windows stack, the list of windows and rectangles returned by the
-- underlying layout and window to be decorated, tupled with its
-- rectangle, produce a Just Rectangle or Nothing if
-- the window is not to be decorated.
decorate :: DecorationStyle ds a => ds a -> Dimension -> Dimension -> Rectangle -> Stack a -> [(a, Rectangle)] -> (a, Rectangle) -> X (Maybe Rectangle)
-- | The default DecorationStyle, with just the default methods'
-- implementations.
data DefaultDecoration a
DefaultDecoration :: DefaultDecoration a
class (Read s, Show s) => Shrinker s
shrinkIt :: Shrinker s => s -> String -> [String]
data DefaultShrinker
shrinkText :: DefaultShrinker
data CustomShrink
CustomShrink :: CustomShrink
shrinkWhile :: (String -> [String]) -> (String -> X Bool) -> String -> X String
-- | True if the window is in the Stack. The Window comes
-- second to facilitate list processing, even though w `isInStack`
-- s won't work...;)
isInStack :: Eq a => Stack a -> a -> Bool
-- | Given a Rectangle and a list of Rectangles is True if
-- the Rectangle is not completely contained by any
-- Rectangle of the list.
isVisible :: Rectangle -> [Rectangle] -> Bool
-- | The contrary of isVisible.
isInvisible :: Rectangle -> [Rectangle] -> Bool
-- | True is the first Rectangle is totally within the second
-- Rectangle.
isWithin :: Rectangle -> Rectangle -> Bool
-- | Short-hand for fromIntegral
fi :: (Integral a, Num b) => a -> b
findWindowByDecoration :: Window -> DecorationState -> Maybe (OrigWin, (Window, Maybe Rectangle))
-- | The Decoration state component, where the list of decorated
-- window's is zipped with a list of decoration. A list of decoration is
-- a list of tuples, a Maybe Window and a 'Maybe
-- Rectangle'. The Window will be displayed only if the rectangle
-- is of type Just.
data DecorationState
type OrigWin = (Window, Rectangle)
instance GHC.Show.Show (XMonad.Layout.Decoration.DefaultDecoration a)
instance GHC.Read.Read (XMonad.Layout.Decoration.DefaultDecoration a)
instance (GHC.Read.Read s, GHC.Read.Read (ds a)) => GHC.Read.Read (XMonad.Layout.Decoration.Decoration ds s a)
instance (GHC.Show.Show s, GHC.Show.Show (ds a)) => GHC.Show.Show (XMonad.Layout.Decoration.Decoration ds s a)
instance GHC.Read.Read XMonad.Layout.Decoration.Theme
instance GHC.Show.Show XMonad.Layout.Decoration.Theme
instance Data.Default.Class.Default XMonad.Layout.Decoration.Theme
instance XMonad.Core.Message XMonad.Layout.Decoration.DecorationMsg
instance GHC.Classes.Eq a => XMonad.Layout.Decoration.DecorationStyle XMonad.Layout.Decoration.DefaultDecoration a
instance (XMonad.Layout.Decoration.DecorationStyle ds Graphics.X11.Types.Window, XMonad.Layout.Decoration.Shrinker s) => XMonad.Layout.LayoutModifier.LayoutModifier (XMonad.Layout.Decoration.Decoration ds s) Graphics.X11.Types.Window
instance GHC.Show.Show XMonad.Layout.Decoration.CustomShrink
instance GHC.Read.Read XMonad.Layout.Decoration.CustomShrink
instance GHC.Show.Show XMonad.Layout.Decoration.DefaultShrinker
instance GHC.Read.Read XMonad.Layout.Decoration.DefaultShrinker
instance XMonad.Layout.Decoration.Shrinker XMonad.Layout.Decoration.DefaultShrinker
-- | A layout modifier to resize windows with the mouse by grabbing the
-- window's lower right corner.
--
-- This module must be used together with
-- XMonad.Layout.WindowArranger.
module XMonad.Actions.MouseResize
mouseResize :: l a -> ModifiedLayout MouseResize l a
data MouseResize a
MR :: [((a, Rectangle), Maybe a)] -> MouseResize a
instance GHC.Show.Show (XMonad.Actions.MouseResize.MouseResize a)
instance GHC.Read.Read (XMonad.Actions.MouseResize.MouseResize a)
instance XMonad.Layout.LayoutModifier.LayoutModifier XMonad.Actions.MouseResize.MouseResize Graphics.X11.Types.Window
-- | A (hopefully) growing collection of themes for decorated layouts.
module XMonad.Util.Themes
listOfThemes :: [ThemeInfo]
ppThemeInfo :: ThemeInfo -> String
-- | The default xmonad theme, by David Roundy.
xmonadTheme :: ThemeInfo
-- | Small decorations with a Ion3 remembrance, by Andrea Rossato.
smallClean :: ThemeInfo
-- | Ffrom Robert Manea's prompt theme.
robertTheme :: ThemeInfo
-- | deifl's Theme, by deifl.
deiflTheme :: ThemeInfo
-- | oxymor00n's theme, by Tom Rauchenwald.
oxymor00nTheme :: ThemeInfo
-- | Don's preferred colors - from DynamicLog...;)
donaldTheme :: ThemeInfo
wfarrTheme :: ThemeInfo
-- | Forest colours, by Kathryn Andersen
kavonForestTheme :: ThemeInfo
-- | Lake (blue/green) colours, by Kathryn Andersen
kavonLakeTheme :: ThemeInfo
-- | Peacock colours, by Kathryn Andersen
kavonPeacockTheme :: ThemeInfo
-- | Violet-Green colours, by Kathryn Andersen
kavonVioGreenTheme :: ThemeInfo
-- | Blue colours, by Kathryn Andersen
kavonBluesTheme :: ThemeInfo
-- | Autumn colours, by Kathryn Andersen
kavonAutumnTheme :: ThemeInfo
-- | Fire colours, by Kathryn Andersen
kavonFireTheme :: ThemeInfo
-- | Christmas colours, by Kathryn Andersen
kavonChristmasTheme :: ThemeInfo
data ThemeInfo
TI :: String -> String -> String -> Theme -> ThemeInfo
[themeName] :: ThemeInfo -> String
[themeAuthor] :: ThemeInfo -> String
[themeDescription] :: ThemeInfo -> String
[theme] :: ThemeInfo -> Theme
-- | This layout modifier will allow to resize windows by dragging their
-- borders with the mouse. However, it only works in layouts or modified
-- layouts that react to the SetGeometry message.
-- XMonad.Layout.WindowArranger can be used to create such a
-- setup, but it is probably must useful in a floating layout such as
-- XMonad.Layout.PositionStoreFloat with which it has been mainly
-- tested. See the documentation of PositionStoreFloat for a typical
-- usage example.
module XMonad.Layout.BorderResize
borderResize :: l a -> ModifiedLayout BorderResize l a
data BorderResize a
BR :: (Map Window RectWithBorders) -> BorderResize a
type RectWithBorders = (Rectangle, [BorderInfo])
data BorderInfo
instance GHC.Read.Read (XMonad.Layout.BorderResize.BorderResize a)
instance GHC.Show.Show (XMonad.Layout.BorderResize.BorderResize a)
instance GHC.Read.Read XMonad.Layout.BorderResize.BorderInfo
instance GHC.Show.Show XMonad.Layout.BorderResize.BorderInfo
instance GHC.Classes.Eq XMonad.Layout.BorderResize.BorderType
instance GHC.Read.Read XMonad.Layout.BorderResize.BorderType
instance GHC.Show.Show XMonad.Layout.BorderResize.BorderType
instance XMonad.Layout.LayoutModifier.LayoutModifier XMonad.Layout.BorderResize.BorderResize Graphics.X11.Types.Window
-- | A layout modifier for decorating windows in a dwm like style.
module XMonad.Layout.DwmStyle
-- | Add simple old dwm-style decorations to windows of a layout.
dwmStyle :: (Eq a, Shrinker s) => s -> Theme -> l a -> ModifiedLayout (Decoration DwmStyle s) l a
-- | A Theme is a record of colors, font etc., to customize a
-- DecorationStyle.
--
-- For a collection of Themes see XMonad.Util.Themes
data Theme
Theme :: String -> String -> String -> String -> String -> String -> String -> String -> String -> String -> Dimension -> Dimension -> [(String, Align)] -> [([[Bool]], Placement)] -> Theme
-- | Color of the active window
[activeColor] :: Theme -> String
-- | Color of the inactive window
[inactiveColor] :: Theme -> String
-- | Color of the urgent window
[urgentColor] :: Theme -> String
-- | Color of the border of the active window
[activeBorderColor] :: Theme -> String
-- | Color of the border of the inactive window
[inactiveBorderColor] :: Theme -> String
-- | Color of the border of the urgent window
[urgentBorderColor] :: Theme -> String
-- | Color of the text of the active window
[activeTextColor] :: Theme -> String
-- | Color of the text of the inactive window
[inactiveTextColor] :: Theme -> String
-- | Color of the text of the urgent window
[urgentTextColor] :: Theme -> String
-- | Font name
[fontName] :: Theme -> String
-- | Maximum width of the decorations (if supported by the
-- DecorationStyle)
[decoWidth] :: Theme -> Dimension
-- | Height of the decorations
[decoHeight] :: Theme -> Dimension
-- | Extra text to appear in a window's title bar. Refer to for a use
-- XMonad.Layout.ImageButtonDecoration
[windowTitleAddons] :: Theme -> [(String, Align)]
-- | Extra icons to appear in a window's title bar. Inner [Bool]
-- is a row in a icon bitmap.
[windowTitleIcons] :: Theme -> [([[Bool]], Placement)]
-- | The default value for this type.
def :: Default a => a
-- | The default xmonad Theme.
-- | Deprecated: Use def (from Data.Default, and re-exported by
-- XMonad.Layout.Decoration) instead.
defaultTheme :: Theme
data DwmStyle a
Dwm :: DwmStyle a
shrinkText :: DefaultShrinker
data CustomShrink
CustomShrink :: CustomShrink
class (Read s, Show s) => Shrinker s
shrinkIt :: Shrinker s => s -> String -> [String]
instance GHC.Read.Read (XMonad.Layout.DwmStyle.DwmStyle a)
instance GHC.Show.Show (XMonad.Layout.DwmStyle.DwmStyle a)
instance GHC.Classes.Eq a => XMonad.Layout.Decoration.DecorationStyle XMonad.Layout.DwmStyle.DwmStyle a
-- | A layout modifier for adding simple decorations to the windows of a
-- given layout. The decorations are in the form of ion-like tabs for
-- window titles.
module XMonad.Layout.SimpleDecoration
-- | Add simple decorations to windows of a layout.
simpleDeco :: (Eq a, Shrinker s) => s -> Theme -> l a -> ModifiedLayout (Decoration SimpleDecoration s) l a
-- | A Theme is a record of colors, font etc., to customize a
-- DecorationStyle.
--
-- For a collection of Themes see XMonad.Util.Themes
data Theme
Theme :: String -> String -> String -> String -> String -> String -> String -> String -> String -> String -> Dimension -> Dimension -> [(String, Align)] -> [([[Bool]], Placement)] -> Theme
-- | Color of the active window
[activeColor] :: Theme -> String
-- | Color of the inactive window
[inactiveColor] :: Theme -> String
-- | Color of the urgent window
[urgentColor] :: Theme -> String
-- | Color of the border of the active window
[activeBorderColor] :: Theme -> String
-- | Color of the border of the inactive window
[inactiveBorderColor] :: Theme -> String
-- | Color of the border of the urgent window
[urgentBorderColor] :: Theme -> String
-- | Color of the text of the active window
[activeTextColor] :: Theme -> String
-- | Color of the text of the inactive window
[inactiveTextColor] :: Theme -> String
-- | Color of the text of the urgent window
[urgentTextColor] :: Theme -> String
-- | Font name
[fontName] :: Theme -> String
-- | Maximum width of the decorations (if supported by the
-- DecorationStyle)
[decoWidth] :: Theme -> Dimension
-- | Height of the decorations
[decoHeight] :: Theme -> Dimension
-- | Extra text to appear in a window's title bar. Refer to for a use
-- XMonad.Layout.ImageButtonDecoration
[windowTitleAddons] :: Theme -> [(String, Align)]
-- | Extra icons to appear in a window's title bar. Inner [Bool]
-- is a row in a icon bitmap.
[windowTitleIcons] :: Theme -> [([[Bool]], Placement)]
-- | The default value for this type.
def :: Default a => a
-- | The default xmonad Theme.
-- | Deprecated: Use def (from Data.Default, and re-exported by
-- XMonad.Layout.Decoration) instead.
defaultTheme :: Theme
data SimpleDecoration a
Simple :: Bool -> SimpleDecoration a
shrinkText :: DefaultShrinker
data CustomShrink
CustomShrink :: CustomShrink
class (Read s, Show s) => Shrinker s
shrinkIt :: Shrinker s => s -> String -> [String]
instance GHC.Read.Read (XMonad.Layout.SimpleDecoration.SimpleDecoration a)
instance GHC.Show.Show (XMonad.Layout.SimpleDecoration.SimpleDecoration a)
instance GHC.Classes.Eq a => XMonad.Layout.Decoration.DecorationStyle XMonad.Layout.SimpleDecoration.SimpleDecoration a
-- | A basic floating layout.
module XMonad.Layout.SimpleFloat
-- | A simple floating layout where every window is placed according to the
-- window's initial attributes.
--
-- This version is decorated with the SimpleDecoration style.
simpleFloat :: Eq a => ModifiedLayout (Decoration SimpleDecoration DefaultShrinker) (ModifiedLayout MouseResize (ModifiedLayout WindowArranger SimpleFloat)) a
-- | Same as simpleFloat, but with the possibility of setting a
-- custom shrinker and a custom theme.
simpleFloat' :: (Eq a, Shrinker s) => s -> Theme -> ModifiedLayout (Decoration SimpleDecoration s) (ModifiedLayout MouseResize (ModifiedLayout WindowArranger SimpleFloat)) a
data SimpleDecoration a
Simple :: Bool -> SimpleDecoration a
data SimpleFloat a
SF :: Dimension -> SimpleFloat a
shrinkText :: DefaultShrinker
data CustomShrink
CustomShrink :: CustomShrink
class (Read s, Show s) => Shrinker s
shrinkIt :: Shrinker s => s -> String -> [String]
instance GHC.Read.Read (XMonad.Layout.SimpleFloat.SimpleFloat a)
instance GHC.Show.Show (XMonad.Layout.SimpleFloat.SimpleFloat a)
instance XMonad.Core.LayoutClass XMonad.Layout.SimpleFloat.SimpleFloat Graphics.X11.Types.Window
-- | Row layout with individually resizable elements.
module XMonad.Layout.ZoomRow
-- | A layout that arranges its windows in a horizontal row, and allows to
-- change the relative size of each element independently.
data ZoomRow f a
-- | ZoomRow layout for laying out elements which are instances of
-- Eq. Perfect for Windows.
zoomRow :: (Eq a, Show a, Read a) => ZoomRow ClassEQ a
-- | The type of messages accepted by a ZoomRow layout
data ZoomMessage
-- | Multiply the focused window's size factor by the given number.
Zoom :: Rational -> ZoomMessage
-- | Set the focused window's size factor to the given number.
ZoomTo :: Rational -> ZoomMessage
-- | Set whether the focused window should occupy all available space when
-- it has focus
ZoomFull :: Bool -> ZoomMessage
-- | Toggle whether the focused window should occupy all available space
-- when it has focus
ZoomFullToggle :: ZoomMessage
-- | Increase the size of the focused window. Defined as Zoom 1.5
zoomIn :: ZoomMessage
-- | Decrease the size of the focused window. Defined as Zoom
-- (2/3)
zoomOut :: ZoomMessage
-- | Reset the size of the focused window. Defined as ZoomTo 1
zoomReset :: ZoomMessage
-- | ZoomRow layout with a custom equality predicate. It should of course
-- satisfy the laws for Eq, and you should also make sure that the
-- layout never has to handle two "equal" elements at the same time (it
-- won't do any huge damage, but might behave a bit strangely).
zoomRowWith :: (EQF f a, Show (f a), Read (f a), Show a, Read a) => f a -> ZoomRow f a
-- | Class for equivalence relations. Must be transitive, reflexive.
class EQF f a
eq :: EQF f a => f a -> a -> a -> Bool
-- | To use the usual ==:
data ClassEQ a
ClassEQ :: ClassEQ a
instance GHC.Show.Show XMonad.Layout.ZoomRow.ZoomMessage
instance (GHC.Classes.Eq a, GHC.Classes.Eq (f a)) => GHC.Classes.Eq (XMonad.Layout.ZoomRow.ZoomRow f a)
instance (GHC.Read.Read a, GHC.Read.Read (f a)) => GHC.Read.Read (XMonad.Layout.ZoomRow.ZoomRow f a)
instance (GHC.Show.Show a, GHC.Show.Show (f a)) => GHC.Show.Show (XMonad.Layout.ZoomRow.ZoomRow f a)
instance GHC.Classes.Eq a => GHC.Classes.Eq (XMonad.Layout.ZoomRow.Elt a)
instance GHC.Read.Read a => GHC.Read.Read (XMonad.Layout.ZoomRow.Elt a)
instance GHC.Show.Show a => GHC.Show.Show (XMonad.Layout.ZoomRow.Elt a)
instance GHC.Classes.Eq (XMonad.Layout.ZoomRow.ClassEQ a)
instance GHC.Read.Read (XMonad.Layout.ZoomRow.ClassEQ a)
instance GHC.Show.Show (XMonad.Layout.ZoomRow.ClassEQ a)
instance GHC.Classes.Eq a => XMonad.Layout.ZoomRow.EQF XMonad.Layout.ZoomRow.ClassEQ a
instance XMonad.Core.Message XMonad.Layout.ZoomRow.ZoomMessage
instance (XMonad.Layout.ZoomRow.EQF f a, GHC.Show.Show a, GHC.Read.Read a, GHC.Show.Show (f a), GHC.Read.Read (f a)) => XMonad.Core.LayoutClass (XMonad.Layout.ZoomRow.ZoomRow f) a
-- | Most basic version of decoration for windows without any additional
-- modifications. In contrast to XMonad.Layout.SimpleDecoration
-- this will result in title bars that span the entire window instead of
-- being only the length of the window title.
module XMonad.Layout.NoFrillsDecoration
-- | Add very simple decorations to windows of a layout.
noFrillsDeco :: (Eq a, Shrinker s) => s -> Theme -> l a -> ModifiedLayout (Decoration NoFrillsDecoration s) l a
data NoFrillsDecoration a
instance GHC.Read.Read (XMonad.Layout.NoFrillsDecoration.NoFrillsDecoration a)
instance GHC.Show.Show (XMonad.Layout.NoFrillsDecoration.NoFrillsDecoration a)
instance GHC.Classes.Eq a => XMonad.Layout.Decoration.DecorationStyle XMonad.Layout.NoFrillsDecoration.NoFrillsDecoration a
-- | A layout transformer to have a layout respect a given screen geometry.
-- Mostly used with Decoration (the Horizontal and the Vertical
-- version will react to SetTheme and change their dimension accordingly.
module XMonad.Layout.ResizeScreen
resizeHorizontal :: Int -> l a -> ModifiedLayout ResizeScreen l a
resizeVertical :: Int -> l a -> ModifiedLayout ResizeScreen l a
resizeHorizontalRight :: Int -> l a -> ModifiedLayout ResizeScreen l a
resizeVerticalBottom :: Int -> l a -> ModifiedLayout ResizeScreen l a
withNewRectangle :: Rectangle -> l a -> ModifiedLayout ResizeScreen l a
data ResizeScreen a
ResizeScreen :: ResizeMode -> Int -> ResizeScreen a
WithNewScreen :: Rectangle -> ResizeScreen a
data ResizeMode
instance GHC.Show.Show (XMonad.Layout.ResizeScreen.ResizeScreen a)
instance GHC.Read.Read (XMonad.Layout.ResizeScreen.ResizeScreen a)
instance GHC.Show.Show XMonad.Layout.ResizeScreen.ResizeMode
instance GHC.Read.Read XMonad.Layout.ResizeScreen.ResizeMode
instance XMonad.Layout.LayoutModifier.LayoutModifier XMonad.Layout.ResizeScreen.ResizeScreen a
-- | A workscreen permits to display a set of workspaces on several
-- screens. In xinerama mode, when a workscreen is viewed, workspaces
-- associated to all screens are visible.
--
-- The first workspace of a workscreen is displayed on first screen,
-- second on second screen, etc. Workspace position can be easily
-- changed. If the current workscreen is called again, workspaces are
-- shifted.
--
-- This also permits to see all workspaces of a workscreen even if just
-- one screen is present, and to move windows from workspace to
-- workscreen.
module XMonad.Actions.Workscreen
-- | Initial configuration of workscreens
configWorkscreen :: [Workscreen] -> X ()
-- | View workscreen of index WorkscreenId. If current workscreen
-- is asked workscreen, workscreen's workspaces are shifted.
viewWorkscreen :: WorkscreenId -> X ()
data Workscreen
Workscreen :: Int -> [WorkspaceId] -> Workscreen
[workscreenId] :: Workscreen -> Int
[workspaces] :: Workscreen -> [WorkspaceId]
-- | Shift a window on the first workspace of workscreen
-- WorkscreenId.
shiftToWorkscreen :: WorkscreenId -> X ()
-- | Create workscreen list from workspace list. Group workspaces to
-- packets of screens number size.
fromWorkspace :: Int -> [WorkspaceId] -> [Workscreen]
-- | Helper to group workspaces. Multiply workspace by screens number.
expandWorkspace :: Int -> [WorkspaceId] -> [WorkspaceId]
instance GHC.Show.Show XMonad.Actions.Workscreen.WorkscreenStorage
instance GHC.Show.Show XMonad.Actions.Workscreen.Workscreen
instance XMonad.Core.ExtensionClass XMonad.Actions.Workscreen.WorkscreenStorage
-- | Ensures that the windows of the current workspace are always in front
-- of windows that are located on other visible screens. This becomes
-- important if you use decoration and drag windows from one screen to
-- another. Using this module, the dragged window will always be in front
-- of other windows.
module XMonad.Hooks.CurrentWorkspaceOnTop
currentWorkspaceOnTop :: X ()
instance XMonad.Core.ExtensionClass XMonad.Hooks.CurrentWorkspaceOnTop.CWOTState
-- | A module for spawning a command once, and only once. Useful to start
-- status bars and make session settings inside startupHook.
module XMonad.Util.SpawnOnce
-- | The first time spawnOnce is executed on a particular command,
-- that command is executed. Subsequent invocations for a command do
-- nothing.
spawnOnce :: String -> X ()
instance GHC.Show.Show XMonad.Util.SpawnOnce.SpawnOnce
instance GHC.Read.Read XMonad.Util.SpawnOnce.SpawnOnce
instance XMonad.Core.ExtensionClass XMonad.Util.SpawnOnce.SpawnOnce
-- | One-shot and permanent ManageHooks that can be updated at runtime.
module XMonad.Hooks.DynamicHooks
-- | Master ManageHook that must be in your xmonad.hs
-- ManageHook.
dynamicMasterHook :: ManageHook
-- | Appends the given ManageHook to the permanent dynamic
-- ManageHook.
addDynamicHook :: ManageHook -> X ()
-- | Modifies the permanent ManageHook with an arbitrary function.
updateDynamicHook :: (ManageHook -> ManageHook) -> X ()
-- | Creates a one-shot ManageHook. Note that you have to specify
-- the two parts of the ManageHook separately. Where you would
-- usually write:
--
-- -- className =? "example" --> doFloat ---- -- you must call oneShotHook as -- --
-- oneShotHook dynHooksRef (className =? "example) doFloat --oneShotHook :: Query Bool -> ManageHook -> X () instance XMonad.Core.ExtensionClass XMonad.Hooks.DynamicHooks.DynamicHooks -- | Hook and keybindings for toggling hook behavior. module XMonad.Hooks.ToggleHook -- | This ManageHook will selectively apply a hook as set by -- hookNext and hookAllNew. toggleHook :: String -> ManageHook -> ManageHook toggleHook' :: String -> ManageHook -> ManageHook -> ManageHook -- | hookNext name True arranges for the next spawned window to -- have the hook name applied, hookNext name False -- cancels it. hookNext :: String -> Bool -> X () toggleHookNext :: String -> X () -- | hookAllNew name True arranges for new windows to have the -- hook name applied, hookAllNew name False cancels it hookAllNew :: String -> Bool -> X () toggleHookAllNew :: String -> X () -- | Query what will happen at the next ManageHook call for the hook -- name. willHook :: String -> X Bool -- | Whether the next window will trigger the hook name. willHookNext :: String -> X Bool -- | Whether new windows will trigger the hook name. willHookAllNew :: String -> X Bool willHookNextPP :: String -> (String -> String) -> X (Maybe String) willHookAllNewPP :: String -> (String -> String) -> X (Maybe String) runLogHook :: X () instance GHC.Show.Show XMonad.Hooks.ToggleHook.HookState instance GHC.Read.Read XMonad.Hooks.ToggleHook.HookState instance XMonad.Core.ExtensionClass XMonad.Hooks.ToggleHook.HookState -- | Hook and keybindings for automatically sending the next spawned -- window(s) to the floating layer. module XMonad.Hooks.FloatNext -- | This ManageHook will selectively float windows as set by -- floatNext and floatAllNew. floatNextHook :: ManageHook -- | floatNext True arranges for the next spawned window to be -- sent to the floating layer, floatNext False cancels it. floatNext :: Bool -> X () toggleFloatNext :: X () -- | floatAllNew True arranges for new windows to be sent to the -- floating layer, floatAllNew False cancels it floatAllNew :: Bool -> X () toggleFloatAllNew :: X () -- | Whether the next window will be set floating willFloatNext :: X Bool -- | Whether new windows will be set floating willFloatAllNew :: X Bool willFloatNextPP :: (String -> String) -> X (Maybe String) willFloatAllNewPP :: (String -> String) -> X (Maybe String) runLogHook :: X () -- | A manageHook and associated logHook for debugging -- ManageHooks. Simplest usage: wrap your xmonad config in the -- debugManageHook combinator. Or use debugManageHookOn -- for a triggerable version, specifying the triggering key sequence in -- EZConfig syntax. Or use the individual hooks in whatever way -- you see fit. module XMonad.Hooks.ManageDebug -- | A combinator to add full ManageHook debugging in a single -- operation. debugManageHook :: XConfig l -> XConfig l -- | A combinator to add triggerable ManageHook debugging in a -- single operation. Specify a key sequence as a string in -- EZConfig syntax; press this key before opening the window to -- get just that logged. debugManageHookOn :: String -> XConfig l -> XConfig l -- | Place this at the start of a ManageHook, or possibly other -- places for a more limited view. It will show the current -- StackSet state and the new window, and set a flag so that -- manageDebugLogHook will display the final StackSet -- state. -- -- Note that the initial state shows only the current workspace; the -- final one shows all workspaces, since your ManageHook might use -- e.g. doShift, manageDebug :: ManageHook -- | manageDebug only if the user requested it with -- debugNextManagedWindow. maybeManageDebug :: ManageHook -- | If manageDebug has set the debug-stack flag, show the stack. manageDebugLogHook :: X () -- | Request that the next window to be managed be manageDebug-ed. -- This can be used anywhere an X action can, such as key bindings, mouse -- bindings (presumably with const), startupHook, etc. debugNextManagedWindow :: X () instance XMonad.Core.ExtensionClass XMonad.Hooks.ManageDebug.ManageStackDebug -- | A utility module to store information about position and size of a -- window. See XMonad.Layout.PositionStoreFloat for a layout that -- makes use of this. module XMonad.Util.PositionStore getPosStore :: X (PositionStore) modifyPosStore :: (PositionStore -> PositionStore) -> X () posStoreInsert :: PositionStore -> Window -> Rectangle -> Rectangle -> PositionStore posStoreMove :: PositionStore -> Window -> Position -> Position -> Rectangle -> Rectangle -> PositionStore posStoreQuery :: PositionStore -> Window -> Rectangle -> Maybe Rectangle posStoreRemove :: PositionStore -> Window -> PositionStore data PositionStore instance GHC.Show.Show XMonad.Util.PositionStore.PositionStore instance GHC.Read.Read XMonad.Util.PositionStore.PositionStore instance GHC.Show.Show XMonad.Util.PositionStore.PosStoreRectangle instance GHC.Read.Read XMonad.Util.PositionStore.PosStoreRectangle instance XMonad.Core.ExtensionClass XMonad.Util.PositionStore.PositionStore -- | A floating layout which has been designed with a dual-head setup in -- mind. It makes use of XMonad.Util.PositionStore as well as -- XMonad.Hooks.PositionStoreHooks . Since there is currently no -- way to move or resize windows with the keyboard alone in this layout, -- it is adviced to use it in combination with a decoration such as -- XMonad.Layout.NoFrillsDecoration (to move windows) and the -- layout modifier XMonad.Layout.BorderResize (to resize windows). module XMonad.Layout.PositionStoreFloat positionStoreFloat :: PositionStoreFloat a data PositionStoreFloat a instance GHC.Read.Read a => GHC.Read.Read (XMonad.Layout.PositionStoreFloat.PositionStoreFloat a) instance GHC.Show.Show a => GHC.Show.Show (XMonad.Layout.PositionStoreFloat.PositionStoreFloat a) instance XMonad.Core.LayoutClass XMonad.Layout.PositionStoreFloat.PositionStoreFloat Graphics.X11.Types.Window -- | Run X () actions by touching the edge of your screen with -- your mouse. module XMonad.Hooks.ScreenCorners data ScreenCorner SCUpperLeft :: ScreenCorner SCUpperRight :: ScreenCorner SCLowerLeft :: ScreenCorner SCLowerRight :: ScreenCorner -- | Add one single X () action to a screen corner addScreenCorner :: ScreenCorner -> X () -> X () -- | Add a list of (ScreenCorner, X ()) tuples addScreenCorners :: [(ScreenCorner, X ())] -> X () -- | Handle screen corner events screenCornerEventHook :: Event -> X All screenCornerLayoutHook :: l a -> ModifiedLayout ScreenCornerLayout l a instance GHC.Show.Show (XMonad.Hooks.ScreenCorners.ScreenCornerLayout a) instance GHC.Read.Read (XMonad.Hooks.ScreenCorners.ScreenCornerLayout a) instance GHC.Show.Show XMonad.Hooks.ScreenCorners.ScreenCorner instance GHC.Classes.Ord XMonad.Hooks.ScreenCorners.ScreenCorner instance GHC.Classes.Eq XMonad.Hooks.ScreenCorners.ScreenCorner instance XMonad.Core.ExtensionClass XMonad.Hooks.ScreenCorners.ScreenCornerState instance XMonad.Layout.LayoutModifier.LayoutModifier XMonad.Hooks.ScreenCorners.ScreenCornerLayout a -- | Log hook which changes the wallpapers depending on visible workspaces. module XMonad.Hooks.WallpaperSetter -- | Add this to your log hook with the workspace configuration as -- argument. wallpaperSetter :: WallpaperConf -> X () -- | Complete wallpaper configuration passed to the hook data WallpaperConf WallpaperConf :: FilePath -> WallpaperList -> WallpaperConf -- | Where the wallpapers reside (if empty, will look in ~/.wallpapers/) [wallpaperBaseDir] :: WallpaperConf -> FilePath -- | List of the wallpaper associations for workspaces [wallpapers] :: WallpaperConf -> WallpaperList -- | Represents a wallpaper data Wallpaper -- | Single, fixed wallpaper WallpaperFix :: FilePath -> Wallpaper -- | Random wallpaper from this subdirectory WallpaperDir :: FilePath -> Wallpaper newtype WallpaperList WallpaperList :: [(WorkspaceId, Wallpaper)] -> WallpaperList -- | default configuration. looks in ~/.wallpapers/ for WORKSPACEID.jpg defWallpaperConf :: WallpaperConf -- | returns the default association list (maps name to name.jpg, -- non-alphanumeric characters are omitted) defWPNames :: [WorkspaceId] -> WallpaperList instance GHC.Read.Read XMonad.Hooks.WallpaperSetter.WallpaperConf instance GHC.Show.Show XMonad.Hooks.WallpaperSetter.WallpaperConf instance GHC.Read.Read XMonad.Hooks.WallpaperSetter.WallpaperList instance GHC.Show.Show XMonad.Hooks.WallpaperSetter.WallpaperList instance GHC.Read.Read XMonad.Hooks.WallpaperSetter.Wallpaper instance GHC.Show.Show XMonad.Hooks.WallpaperSetter.Wallpaper instance GHC.Classes.Eq XMonad.Hooks.WallpaperSetter.Wallpaper instance XMonad.Core.ExtensionClass XMonad.Hooks.WallpaperSetter.WCState instance GHC.Base.Monoid XMonad.Hooks.WallpaperSetter.WallpaperList instance Data.Default.Class.Default XMonad.Hooks.WallpaperSetter.WallpaperConf -- | A module for spawning a pipe whose Handle lives in the Xmonad -- state. module XMonad.Util.SpawnNamedPipe -- | When spawnNamedPipe is executed with a command String -- and a name String respectively. The command string is spawned -- with spawnPipe (as long as the name chosen hasn't been used -- already) and the Handle returned is saved in Xmonad's state -- associated with the name String. spawnNamedPipe :: String -> String -> X () -- | Attempts to retrieve a Handle to a pipe previously stored in -- Xmonad's state associated with the given string via a call to -- spawnNamedPipe. If the given string doesn't exist in the map -- stored in Xmonad's state Nothing is returned. getNamedPipe :: String -> X (Maybe Handle) instance GHC.Show.Show XMonad.Util.SpawnNamedPipe.NamedPipes instance XMonad.Core.ExtensionClass XMonad.Util.SpawnNamedPipe.NamedPipes -- | Dwm-like swap function for xmonad. -- -- Swaps focused window with the master window. If focus is in the -- master, swap it with the next window in the stack. Focus stays in the -- master. module XMonad.Actions.DwmPromote -- | Swap the focused window with the master window. If focus is in the -- master, swap it with the next window in the stack. Focus stays in the -- master. dwmpromote :: X () -- | This module provides a method to cease management of a window without -- unmapping it. This is especially useful for applications like kicker -- and gnome-panel. See also XMonad.Hooks.ManageDocks for more a -- more automated solution. -- -- To make a panel display correctly with xmonad: -- --
-- instance XPrompt Shell where -- showXPrompt Shell = "Run: " --class XPrompt t where nextCompletion = getNextOfLastWord commandToComplete _ = getLastWord completionToCommand _ c = c completionFunction t = \ _ -> return ["Completions for " ++ (showXPrompt t) ++ " could not be loaded"] modeAction _ _ _ = return () -- | This method is used to print the string to be displayed in the command -- line window. showXPrompt :: XPrompt t => t -> String -- | This method is used to generate the next completion to be printed in -- the command line when tab is pressed, given the string presently in -- the command line and the list of completion. This function is not used -- when in multiple modes (because alwaysHighlight in XPConfig is True) nextCompletion :: XPrompt t => t -> String -> [String] -> String -- | This method is used to generate the string to be passed to the -- completion function. commandToComplete :: XPrompt t => t -> String -> String -- | This method is used to process each completion in order to generate -- the string that will be compared with the command presently displayed -- in the command line. If the prompt is using getNextOfLastWord -- for implementing nextCompletion (the default implementation), -- this method is also used to generate, from the returned completion, -- the string that will form the next command line when tab is pressed. completionToCommand :: XPrompt t => t -> String -> String -- | When the prompt has multiple modes, this is the function used to -- generate the autocompletion list. The argument passed to this function -- is given by commandToComplete The default implementation shows -- an error message. completionFunction :: XPrompt t => t -> ComplFunction -- | When the prompt has multiple modes (created with mkXPromptWithModes), -- this function is called when the user picks an item from the -- autocompletion list. The first argument is the prompt (or mode) on -- which the item was picked The first string argument is the -- autocompleted item's text. The second string argument is the query -- made by the user (written in the prompt's buffer). See -- XMonadActionsLauncher.hs for a usage example. modeAction :: XPrompt t => t -> String -> String -> X () type XP = StateT XPState IO -- | Default key bindings for prompts. Click on the "Source" link to the -- right to see the complete list. See also defaultXPKeymap'. defaultXPKeymap :: Map (KeyMask, KeySym) (XP ()) -- | A variant of defaultXPKeymap which lets you specify a custom -- predicate for identifying non-word characters, which affects all the -- word-oriented commands (move/kill word). The default is -- isSpace. For example, by default a path like -- foo/bar/baz would be considered as a single word. You could -- use a predicate like (\c -> isSpace c || c == '/') to move -- through or delete components of the path one at a time. defaultXPKeymap' :: (Char -> Bool) -> Map (KeyMask, KeySym) (XP ()) -- | A keymap with many emacs-like key bindings. Click on the "Source" link -- to the right to see the complete list. See also -- emacsLikeXPKeymap'. emacsLikeXPKeymap :: Map (KeyMask, KeySym) (XP ()) -- | A variant of emacsLikeXPKeymap which lets you specify a custom -- predicate for identifying non-word characters, which affects all the -- word-oriented commands (move/kill word). The default is -- isSpace. For example, by default a path like -- foo/bar/baz would be considered as a single word. You could -- use a predicate like (\c -> isSpace c || c == '/') to move -- through or delete components of the path one at a time. emacsLikeXPKeymap' :: (Char -> Bool) -> Map (KeyMask, KeySym) (XP ()) -- | Quit. quit :: XP () -- | Kill the portion of the command before the cursor killBefore :: XP () -- | Kill the portion of the command including and after the cursor killAfter :: XP () -- | Put the cursor at the start of line startOfLine :: XP () -- | Put the cursor at the end of line endOfLine :: XP () -- | Insert the current X selection string at the cursor position. pasteString :: XP () -- | move the cursor one position moveCursor :: Direction1D -> XP () -- | Sets the input string to the given value. setInput :: String -> XP () -- | Returns the current input string. Intented for use in custom keymaps -- where the get or similar can't be used to retrieve it. getInput :: XP String -- | Move the cursor one word, using isSpace as the default -- predicate for non-word characters. See moveWord'. moveWord :: Direction1D -> XP () -- | Move the cursor one word, given a predicate to identify non-word -- characters. First move past any consecutive non-word characters; then -- move to just before the next non-word character. moveWord' :: (Char -> Bool) -> Direction1D -> XP () -- | Kill the next/previous word, using isSpace as the default -- predicate for non-word characters. See killWord'. killWord :: Direction1D -> XP () -- | Kill the next/previous word, given a predicate to identify non-word -- characters. First delete any consecutive non-word characters; then -- delete consecutive word characters, stopping just before the next -- non-word character. -- -- For example, by default (using killWord) a path like -- foo/bar/baz would be deleted in its entirety. Instead you can -- use something like killWord' (\c -> isSpace c || c == '/') -- to delete the path one component at a time. killWord' :: (Char -> Bool) -> Direction1D -> XP () -- | Remove a character at the cursor position deleteString :: Direction1D -> XP () moveHistory :: (Stack String -> Stack String) -> XP () setSuccess :: Bool -> XP () setDone :: Bool -> XP () -- | One-dimensional directions: data Direction1D Next :: Direction1D Prev :: Direction1D type ComplFunction = String -> IO [String] -- | Creates a window with the attribute override_redirect set to True. -- Windows Managers should not touch this kind of windows. mkUnmanagedWindow :: Display -> Screen -> Window -> Position -> Position -> Dimension -> Dimension -> IO Window -- | Fills a Drawable with a rectangle and a border fillDrawable :: Display -> Drawable -> GC -> Pixel -> Pixel -> Dimension -> Dimension -> Dimension -> IO () -- | This function takes a list of possible completions and returns a -- completions function to be used with mkXPrompt mkComplFunFromList :: [String] -> String -> IO [String] -- | This function takes a list of possible completions and returns a -- completions function to be used with mkXPrompt. If the string -- is null it will return all completions. mkComplFunFromList' :: [String] -> String -> IO [String] -- | Given the prompt type, the command line and the completion list, -- return the next completion in the list for the last word of the -- command line. This is the default nextCompletion -- implementation. getNextOfLastWord :: XPrompt t => t -> String -> [String] -> String -- | An alternative nextCompletion implementation: given a command -- and a completion list, get the next completion in the list matching -- the whole command line. getNextCompletion :: String -> [String] -> String -- | Gets the last word of a string or the whole string if formed by only -- one word getLastWord :: String -> String -- | Skips the last word of the string, if the string is composed by more -- then one word. Otherwise returns the string. skipLastWord :: String -> String -- | Given a maximum length, splits a list into sublists splitInSubListsAt :: Int -> [a] -> [[a]] breakAtSpace :: String -> (String, String) -- | Sort a list and remove duplicates. Like deleteAllDuplicates, -- but trades off laziness and stability for efficiency. uniqSort :: Ord a => [a] -> [a] -- | historyCompletion provides a canned completion function much -- like getShellCompl; you pass it to mkXPrompt, and it will -- make completions work from the query history stored in -- ~/.xmonad/history. historyCompletion :: ComplFunction -- | Like historyCompletion but only uses history data from Prompts -- whose name satisfies the given predicate. historyCompletionP :: (String -> Bool) -> ComplFunction -- | Functions to be used with the historyFilter setting. -- deleteAllDuplicates will remove all duplicate entries. -- deleteConsecutive will only remove duplicate elements -- immediately next to each other. deleteAllDuplicates :: [String] -> [String] -- | Functions to be used with the historyFilter setting. -- deleteAllDuplicates will remove all duplicate entries. -- deleteConsecutive will only remove duplicate elements -- immediately next to each other. deleteConsecutive :: [String] -> [String] data HistoryMatches -- | Initializes a new HistoryMatches structure to be passed to -- historyUpMatching initMatches :: (Functor m, MonadIO m) => m HistoryMatches -- | Retrieve the next history element that starts with the current input. -- Pass it the result of initMatches when creating the prompt. Example: -- --
-- ..
-- ((modMask,xK_p), shellPrompt . myPrompt =<< initMatches)
-- ..
-- myPrompt ref = def
-- { promptKeymap = M.union [((0,xK_Up), historyUpMatching ref)
-- ,((0,xK_Down), historyDownMatching ref)]
-- (promptKeymap def)
-- , .. }
--
historyUpMatching :: HistoryMatches -> XP ()
-- | Retrieve the next history element that starts with the current input.
-- Pass it the result of initMatches when creating the prompt. Example:
--
--
-- ..
-- ((modMask,xK_p), shellPrompt . myPrompt =<< initMatches)
-- ..
-- myPrompt ref = def
-- { promptKeymap = M.union [((0,xK_Up), historyUpMatching ref)
-- ,((0,xK_Down), historyDownMatching ref)]
-- (promptKeymap def)
-- , .. }
--
historyDownMatching :: HistoryMatches -> XP ()
data XPState
instance GHC.Read.Read XMonad.Prompt.XPPosition
instance GHC.Show.Show XMonad.Prompt.XPPosition
instance GHC.Show.Show XMonad.Prompt.XPType
instance XMonad.Prompt.XPrompt XMonad.Prompt.XPType
instance Data.Default.Class.Default XMonad.Prompt.XPConfig
-- | A workspace prompt for XMonad
module XMonad.Prompt.Workspace
workspacePrompt :: XPConfig -> (String -> X ()) -> X ()
data Wor
Wor :: String -> Wor
instance XMonad.Prompt.XPrompt XMonad.Prompt.Workspace.Wor
-- | Provides bindings to add and delete workspaces.
module XMonad.Actions.DynamicWorkspaces
-- | Add a new workspace with the given name, or do nothing if a workspace
-- with the given name already exists; then switch to the newly created
-- workspace.
addWorkspace :: String -> X ()
-- | Prompt for the name of a new workspace, add it if it does not already
-- exist, and switch to it.
addWorkspacePrompt :: XPConfig -> X ()
-- | Same as addWorkspace, but adds the workspace to the end of the list of
-- workspaces
appendWorkspace :: String -> X ()
-- | Prompt for the name of a new workspace, appending it to the end of the
-- list of workspaces if it does not already exist, and switch to it.
appendWorkspacePrompt :: XPConfig -> X ()
-- | Adds a new workspace with the given name to the current list of
-- workspaces. This function allows the user to pass a function that
-- inserts an element into a list at an arbitrary spot.
addWorkspaceAt :: (WindowSpace -> [WindowSpace] -> [WindowSpace]) -> String -> X ()
-- | Remove the current workspace.
removeWorkspace :: X ()
-- | Remove workspace with specific tag.
removeWorkspaceByTag :: String -> X ()
-- | Remove the current workspace if it contains no windows.
removeEmptyWorkspace :: X ()
-- | Remove the current workspace after an operation if it is empty and
-- hidden. Can be used to remove a workspace if it is empty when leaving
-- it. The operation may only change workspace once, otherwise the
-- workspace will not be removed.
removeEmptyWorkspaceAfter :: X () -> X ()
-- | Like removeEmptyWorkspaceAfter but use a list of sticky
-- workspaces, whose entries will never be removed.
removeEmptyWorkspaceAfterExcept :: [String] -> X () -> X ()
-- | Add a new hidden workspace with the given name, or do nothing if a
-- workspace with the given name already exists.
addHiddenWorkspace :: String -> X ()
-- | Add a new hidden workspace with the given name, or do nothing if a
-- workspace with the given name already exists. Takes a function to
-- insert the workspace at an arbitrary spot in the list.
addHiddenWorkspaceAt :: (WindowSpace -> [WindowSpace] -> [WindowSpace]) -> String -> X ()
withWorkspace :: XPConfig -> (String -> X ()) -> X ()
selectWorkspace :: XPConfig -> X ()
renameWorkspace :: XPConfig -> X ()
renameWorkspaceByName :: String -> X ()
toNthWorkspace :: (String -> X ()) -> Int -> X ()
withNthWorkspace :: (String -> WindowSet -> WindowSet) -> Int -> X ()
-- | Dynamically manage "workspace groups", sets of workspaces being used
-- together for some common task or purpose, to allow switching between
-- workspace groups in a single action. Note that this only makes sense
-- for multi-head setups.
module XMonad.Actions.DynamicWorkspaceGroups
type WSGroupId = String
-- | Add a new workspace group of the given name, mapping to an explicitly
-- specified association between screen IDs and workspace names. This
-- function could be useful for, say, creating some standard workspace
-- groups in your startup hook.
addRawWSGroup :: WSGroupId -> [(ScreenId, WorkspaceId)] -> X ()
-- | Add a new workspace group with the given name.
addWSGroup :: WSGroupId -> [WorkspaceId] -> X ()
-- | Give a name to the current workspace group.
addCurrentWSGroup :: WSGroupId -> X ()
-- | Delete the named workspace group from the list of workspace groups.
-- Note that this has no effect on the workspaces involved; it simply
-- forgets the given name.
forgetWSGroup :: WSGroupId -> X ()
-- | View the workspace group with the given name.
viewWSGroup :: WSGroupId -> X ()
-- | Prompt for a workspace group to view.
promptWSGroupView :: XPConfig -> String -> X ()
-- | Prompt for a name for the current workspace group.
promptWSGroupAdd :: XPConfig -> String -> X ()
-- | Prompt for a workspace group to forget.
promptWSGroupForget :: XPConfig -> String -> X ()
data WSGPrompt
instance GHC.Show.Show XMonad.Actions.DynamicWorkspaceGroups.WSGroupStorage
instance GHC.Read.Read XMonad.Actions.DynamicWorkspaceGroups.WSGroupStorage
instance XMonad.Core.ExtensionClass XMonad.Actions.DynamicWorkspaceGroups.WSGroupStorage
instance XMonad.Prompt.XPrompt XMonad.Actions.DynamicWorkspaceGroups.WSGPrompt
-- | A directory prompt for XMonad
module XMonad.Prompt.Directory
directoryPrompt :: XPConfig -> String -> (String -> X ()) -> X ()
data Dir
instance XMonad.Prompt.XPrompt XMonad.Prompt.Directory.Dir
-- | Imbues workspaces with additional features so they can be treated as
-- individual project areas.
module XMonad.Actions.DynamicProjects
-- | Details about a workspace that represents a project.
data Project
Project :: !ProjectName -> !FilePath -> !(Maybe (X ())) -> Project
-- | Workspace name.
[projectName] :: Project -> !ProjectName
-- | Working directory.
[projectDirectory] :: Project -> !FilePath
-- | Optional start-up hook.
[projectStartHook] :: Project -> !(Maybe (X ()))
type ProjectName = String
-- | Add dynamic projects support to the given config.
dynamicProjects :: [Project] -> XConfig a -> XConfig a
-- | Prompt for a project name and then switch to it. Automatically creates
-- a project if a new name is returned from the prompt.
switchProjectPrompt :: XPConfig -> X ()
-- | Prompts for a project name and then shifts the currently focused
-- window to that project.
shiftToProjectPrompt :: XPConfig -> X ()
-- | Rename the current project.
renameProjectPrompt :: XPConfig -> X ()
-- | Switch to the given project.
switchProject :: Project -> X ()
-- | Shift the currently focused window to the given project.
shiftToProject :: Project -> X ()
-- | Find a project based on its name.
lookupProject :: ProjectName -> X (Maybe Project)
-- | Fetch the current project (the one being used for the currently active
-- workspace).
currentProject :: X Project
-- | Activate a project by updating the working directory and possibly
-- running its start-up hook. This function is automatically invoked when
-- the workspace changes.
activateProject :: Project -> X ()
instance XMonad.Core.ExtensionClass XMonad.Actions.DynamicProjects.ProjectState
-- | A set of prompts for XMonad
module XMonad.Actions.Launcher
-- | Create a list of modes based on : a list of extensions mapped to
-- actions the path to hoogle
defaultLauncherModes :: LauncherConfig -> [XPMode]
type ExtensionActions = Map String (String -> X ())
data LauncherConfig
LauncherConfig :: String -> String -> LauncherConfig
[browser] :: LauncherConfig -> String
[pathToHoogle] :: LauncherConfig -> String
-- | Creates a prompt with the given modes
launcherPrompt :: XPConfig -> [XPMode] -> X ()
instance XMonad.Prompt.XPrompt XMonad.Actions.Launcher.CalculatorMode
instance XMonad.Prompt.XPrompt XMonad.Actions.Launcher.HoogleMode
-- | A shell prompt for XMonad
module XMonad.Prompt.Shell
data Shell
Shell :: Shell
shellPrompt :: XPConfig -> X ()
prompt :: FilePath -> XPConfig -> X ()
safePrompt :: FilePath -> XPConfig -> X ()
unsafePrompt :: FilePath -> XPConfig -> X ()
getCommands :: IO [String]
-- | Ask the shell what browser the user likes. If the user hasn't defined
-- any $BROWSER, defaults to returning "firefox", since that seems to be
-- the most common X web browser. Note that if you don't specify a GUI
-- browser but a textual one, that'll be a problem as getBrowser
-- will be called by functions expecting to be able to just execute the
-- string or pass it to a shell; so in that case, define $BROWSER as
-- something like "xterm -e elinks" or as the name of a shell script
-- doing much the same thing.
getBrowser :: IO String
-- | Like getBrowser, but should be of a text editor. This gets the
-- $EDITOR variable, defaulting to "emacs".
getEditor :: IO String
getShellCompl :: [String] -> Predicate -> String -> IO [String]
split :: Eq a => a -> [a] -> [[a]]
instance XMonad.Prompt.XPrompt XMonad.Prompt.Shell.Shell
module XMonad.Actions.Search
-- | Given a browser, a search engine's transformation function, and a
-- search term, perform the requested search in the browser.
search :: Browser -> Site -> Query -> X ()
data SearchEngine
SearchEngine :: Name -> Site -> SearchEngine
-- | Given a base URL, create the SearchEngine that escapes the
-- query and appends it to the base. You can easily define a new engine
-- locally using exported functions without needing to modify
-- XMonad.Actions.Search:
--
-- -- myNewEngine = searchEngine "site" "http://site.com/search=" ---- -- The important thing is that the site has a interface which accepts the -- escaped query string as part of the URL. Alas, the exact URL to feed -- searchEngine varies from site to site, often considerably, so there's -- no general way to cover this. -- -- Generally, examining the resultant URL of a search will allow you to -- reverse-engineer it if you can't find the necessary URL already -- described in other projects such as Surfraw. searchEngine :: Name -> String -> SearchEngine -- | If your search engine is more complex than this (you may want to -- identify the kind of input and make the search URL dependent on the -- input or put the query inside of a URL instead of in the end) you can -- use the alternative searchEngineF function. -- --
-- searchFunc :: String -> String -- searchFunc s | "wiki:" `isPrefixOf` s = "http://en.wikipedia.org/wiki/" ++ (escape $ tail $ snd $ break (==':') s) -- | "http://" `isPrefixOf` s = s -- | otherwise = (use google) s -- myNewEngine = searchEngineF "mymulti" searchFunc ---- -- searchFunc here searches for a word in wikipedia if it has a -- prefix of "wiki:" (you can use the escape function to escape -- any forbidden characters), opens an address directly if it starts with -- "http://" and otherwise uses the provided google search engine. You -- can use other engines inside of your own through the use -- function as shown above to make complex searches. -- -- The user input will be automatically escaped in search engines created -- with searchEngine, searchEngineF, however, completely -- depends on the transformation function passed to it. searchEngineF :: Name -> Site -> SearchEngine -- | Like search, but in this case, the string is not specified but -- grabbed from the user's response to a prompt. Example: -- --
-- , ((modm, xK_g), promptSearch greenXPConfig google) ---- -- This specializes "promptSearchBrowser" by supplying the browser -- argument as supplied by getBrowser from -- XMonad.Prompt.Shell. promptSearch :: XPConfig -> SearchEngine -> X () -- | Like search, but for use with the output from a Prompt; it -- grabs the Prompt's result, passes it to a given searchEngine and opens -- it in a given browser. promptSearchBrowser :: XPConfig -> Browser -> SearchEngine -> X () -- | Like search, but for use with the X selection; it grabs the -- selection, passes it to a given searchEngine and opens it in the -- default browser . Example: -- --
-- , ((modm .|. shiftMask, xK_g), selectSearch google) ---- -- This specializes "selectSearchBrowser" by supplying the browser -- argument as supplied by getBrowser from -- XMonad.Prompt.Shell. selectSearch :: SearchEngine -> X () -- | Like search, but for use with the X selection; it grabs the -- selection, passes it to a given searchEngine and opens it in a given -- browser. selectSearchBrowser :: Browser -> SearchEngine -> X () -- | The isPrefixOf function takes two lists and returns True -- iff the first list is a prefix of the second. isPrefixOf :: Eq a => [a] -> [a] -> Bool -- | Escape the search string so search engines understand it. Only digits -- and ASCII letters are not encoded. All non ASCII characters which are -- encoded as UTF8 escape :: String -> String -- | Given an already defined search engine, extracts its transformation -- function, making it easy to create compound search engines. For an -- instance you can use use google to get a function which makes -- the same transformation as the google search engine would. use :: SearchEngine -> Site -- | This function wraps up a search engine and creates a new one, which -- works like the argument, but goes directly to a URL if one is given -- rather than searching. -- --
-- myIntelligentGoogleEngine = intelligent google ---- -- Now if you search for http://xmonad.org it will directly open in your -- browser intelligent :: SearchEngine -> SearchEngine -- | Connects a few search engines into one. If the search engines' names -- are "s1", "s2" and "s3", then the resulting engine will use s1 if the -- query is s1:word, s2 if you type s2:word and s3 in -- all other cases. -- -- Example: -- --
-- multiEngine = intelligent (wikipedia !> mathworld !> (prefixAware google)) ---- -- Now if you type "wiki:Haskell" it will search for "Haskell" in -- Wikipedia, "mathworld:integral" will search mathworld, and everything -- else will fall back to google. The use of intelligent will make sure -- that URLs are opened directly. (!>) :: SearchEngine -> SearchEngine -> SearchEngine -- | Makes a search engine prefix-aware. Especially useful together with -- !>. It will automatically remove the prefix from a query so -- that you don't end up searching for google:xmonad if google is your -- fallback engine and you explicitly add the prefix. prefixAware :: SearchEngine -> SearchEngine -- | Changes search engine's name namedEngine :: Name -> SearchEngine -> SearchEngine amazon :: SearchEngine alpha :: SearchEngine codesearch :: SearchEngine deb :: SearchEngine debbts :: SearchEngine debpts :: SearchEngine dictionary :: SearchEngine google :: SearchEngine hackage :: SearchEngine hoogle :: SearchEngine images :: SearchEngine imdb :: SearchEngine isohunt :: SearchEngine lucky :: SearchEngine maps :: SearchEngine mathworld :: SearchEngine openstreetmap :: SearchEngine scholar :: SearchEngine stackage :: SearchEngine thesaurus :: SearchEngine wayback :: SearchEngine wikipedia :: SearchEngine wiktionary :: SearchEngine youtube :: SearchEngine vocabulary :: SearchEngine duckduckgo :: SearchEngine multi :: SearchEngine type Browser = FilePath type Site = String -> String type Query = String type Name = String -- | A customized prompt indicating we are searching, and the name of the -- site. data Search instance XMonad.Prompt.XPrompt XMonad.Actions.Search.Search -- | Provides a way to modify a window spawned by a command(e.g shift it to -- the workspace it was launched on) by using the _NET_WM_PID property -- that most windows set on creation. Hence this module won't work on -- applications that don't set this property. module XMonad.Actions.SpawnOn data Spawner -- | Provides a manage hook to react on process spawned with -- spawnOn, spawnHere etc. manageSpawn :: ManageHook manageSpawnWithGC :: ([(ProcessID, ManageHook)] -> X [(ProcessID, ManageHook)]) -> ManageHook -- | Replacement for spawn which launches application on current -- workspace. spawnHere :: String -> X () -- | Replacement for spawn which launches application on given -- workspace. spawnOn :: WorkspaceId -> String -> X () -- | Spawn an application and apply the manage hook when it opens. spawnAndDo :: ManageHook -> String -> X () -- | Replacement for Shell prompt (XMonad.Prompt.Shell) which -- launches application on current workspace. shellPromptHere :: XPConfig -> X () -- | Replacement for Shell prompt (XMonad.Prompt.Shell) which -- launches application on given workspace. shellPromptOn :: WorkspaceId -> XPConfig -> X () instance XMonad.Core.ExtensionClass XMonad.Actions.SpawnOn.Spawner -- | Functions for tagging windows and selecting them by tags. module XMonad.Actions.TagWindows -- | add a tag to the existing ones addTag :: String -> Window -> X () -- | remove a tag from a window, if it exists delTag :: String -> Window -> X () -- | remove all tags unTag :: Window -> X () -- | set multiple tags for a window at once (overriding any previous tags) setTags :: [String] -> Window -> X () -- | read all tags of a window reads from the "_XMONAD_TAGS" window -- property getTags :: Window -> X [String] -- | check a window for the given tag hasTag :: String -> Window -> X Bool -- | apply a pure function to windows with a tag withTaggedP :: String -> (Window -> WindowSet -> WindowSet) -> X () -- | apply a pure function to windows with a tag withTaggedGlobalP :: String -> (Window -> WindowSet -> WindowSet) -> X () withFocusedP :: (Window -> WindowSet -> WindowSet) -> X () withTagged :: String -> (Window -> X ()) -> X () withTaggedGlobal :: String -> (Window -> X ()) -> X () -- | Move the focus in a group of windows, which share the same given tag. -- The Global variants move through all workspaces, whereas the other -- ones operate only on the current workspace focusUpTagged :: String -> X () -- | Move the focus in a group of windows, which share the same given tag. -- The Global variants move through all workspaces, whereas the other -- ones operate only on the current workspace focusUpTaggedGlobal :: String -> X () -- | Move the focus in a group of windows, which share the same given tag. -- The Global variants move through all workspaces, whereas the other -- ones operate only on the current workspace focusDownTagged :: String -> X () -- | Move the focus in a group of windows, which share the same given tag. -- The Global variants move through all workspaces, whereas the other -- ones operate only on the current workspace focusDownTaggedGlobal :: String -> X () shiftHere :: (Ord a, Eq s, Eq i) => a -> StackSet i l a s sd -> StackSet i l a s sd shiftToScreen :: (Ord a, Eq s, Eq i) => s -> a -> StackSet i l a s sd -> StackSet i l a s sd tagPrompt :: XPConfig -> (String -> X ()) -> X () tagDelPrompt :: XPConfig -> X () data TagPrompt instance XMonad.Prompt.XPrompt XMonad.Actions.TagWindows.TagPrompt -- | A ssh prompt for XMonad module XMonad.Prompt.Ssh sshPrompt :: XPConfig -> X () data Ssh instance XMonad.Prompt.XPrompt XMonad.Prompt.Ssh.Ssh -- | A prompt for changing the theme of the current workspace module XMonad.Prompt.Theme themePrompt :: XPConfig -> X () data ThemePrompt instance XMonad.Prompt.XPrompt XMonad.Prompt.Theme.ThemePrompt -- | WorkspaceDir is an extension to set the current directory in a -- workspace. -- -- Actually, it sets the current directory in a layout, since there's no -- way I know of to attach a behavior to a workspace. This means that any -- terminals (or other programs) pulled up in that workspace (with that -- layout) will execute in that working directory. Sort of handy, I -- think. -- -- Note this extension requires the directory package to be -- installed. module XMonad.Layout.WorkspaceDir workspaceDir :: LayoutClass l a => String -> l a -> ModifiedLayout WorkspaceDir l a changeDir :: XPConfig -> X () data WorkspaceDir a instance GHC.Show.Show (XMonad.Layout.WorkspaceDir.WorkspaceDir a) instance GHC.Read.Read (XMonad.Layout.WorkspaceDir.WorkspaceDir a) instance XMonad.Core.Message XMonad.Layout.WorkspaceDir.Chdir instance XMonad.Layout.LayoutModifier.LayoutModifier XMonad.Layout.WorkspaceDir.WorkspaceDir Graphics.X11.Types.Window -- | A layout modifier to add a bar of tabs to your layouts. module XMonad.Layout.TabBarDecoration -- | Add, on the top of the screen, a simple bar of tabs to a given | -- layout, with the default theme and the default shrinker. simpleTabBar :: Eq a => l a -> ModifiedLayout (Decoration TabBarDecoration DefaultShrinker) (ModifiedLayout ResizeScreen l) a -- | Same of simpleTabBar, but with the possibility of setting a -- custom shrinker, a custom theme and the position: Top or -- Bottom. tabBar :: (Eq a, Shrinker s) => s -> Theme -> XPPosition -> l a -> ModifiedLayout (Decoration TabBarDecoration s) l a -- | The default value for this type. def :: Default a => a -- | The default xmonad Theme. -- | Deprecated: Use def (from Data.Default, and re-exported by -- XMonad.Layout.Decoration) instead. defaultTheme :: Theme shrinkText :: DefaultShrinker data TabBarDecoration a TabBar :: XPPosition -> TabBarDecoration a data XPPosition Top :: XPPosition Bottom :: XPPosition instance GHC.Show.Show (XMonad.Layout.TabBarDecoration.TabBarDecoration a) instance GHC.Read.Read (XMonad.Layout.TabBarDecoration.TabBarDecoration a) instance GHC.Classes.Eq a => XMonad.Layout.Decoration.DecorationStyle XMonad.Layout.TabBarDecoration.TabBarDecoration a -- | A collection of decorated layouts: some of them may be nice, some -- usable, others just funny. module XMonad.Layout.DecorationMadness -- | A Circle layout with the xmonad default decoration, default -- theme and default shrinker. -- -- Here you can find a screen shot: -- -- -- http://code.haskell.org/~arossato/xmonadShots/circleSimpleDefault.png circleSimpleDefault :: ModifiedLayout (Decoration DefaultDecoration DefaultShrinker) Circle Window -- | Similar to circleSimpleDefault but with the possibility of -- setting a custom shrinker and a custom theme. circleDefault :: Shrinker s => s -> Theme -> ModifiedLayout (Decoration DefaultDecoration s) Circle Window -- | A Circle layout with the xmonad default decoration, default -- theme and default shrinker, but with the possibility of moving windows -- with the mouse, and resize/move them with the keyboard. -- -- Here you can find a screen shot: -- -- -- http://code.haskell.org/~arossato/xmonadShots/circleSimpleDefaultResizable.png circleSimpleDefaultResizable :: ModifiedLayout (Decoration DefaultDecoration DefaultShrinker) (ModifiedLayout MouseResize (ModifiedLayout WindowArranger Circle)) Window -- | Similar to circleSimpleDefaultResizable but with the -- possibility of setting a custom shrinker and a custom theme. circleDefaultResizable :: Shrinker s => s -> Theme -> ModifiedLayout (Decoration DefaultDecoration s) (ModifiedLayout MouseResize (ModifiedLayout WindowArranger Circle)) Window -- | A Circle layout with the xmonad simple decoration, default -- theme and default shrinker. -- -- Here you can find a screen shot: -- -- -- http://code.haskell.org/~arossato/xmonadShots/circleSimpleDeco.png circleSimpleDeco :: ModifiedLayout (Decoration SimpleDecoration DefaultShrinker) Circle Window -- | A Circle layout with the xmonad simple decoration, default -- theme and default shrinker, but with the possibility of moving windows -- with the mouse, and resize/move them with the keyboard. -- -- Here you can find a screen shot: -- -- -- http://code.haskell.org/~arossato/xmonadShots/circleSimpleDecoResizable.png circleSimpleDecoResizable :: ModifiedLayout (Decoration SimpleDecoration DefaultShrinker) (ModifiedLayout MouseResize (ModifiedLayout WindowArranger Circle)) Window -- | Similar to circleSimpleDece but with the possibility of -- setting a custom shrinker and a custom theme. circleDeco :: Shrinker s => s -> Theme -> ModifiedLayout (Decoration SimpleDecoration s) Circle Window -- | Similar to circleSimpleDecoResizable but with the possibility -- of setting a custom shrinker and a custom theme. circleDecoResizable :: Shrinker s => s -> Theme -> ModifiedLayout (Decoration SimpleDecoration s) (ModifiedLayout MouseResize (ModifiedLayout WindowArranger Circle)) Window -- | A Circle layout with the xmonad DwmStyle decoration, default -- theme and default shrinker. -- -- Here you can find a screen shot: -- -- -- http://code.haskell.org/~arossato/xmonadShots/circleSimpleDwmStyle.png circleSimpleDwmStyle :: ModifiedLayout (Decoration DwmStyle DefaultShrinker) Circle Window -- | Similar to circleSimpleDwmStyle but with the possibility of -- setting a custom shrinker and a custom theme. circleDwmStyle :: Shrinker s => s -> Theme -> ModifiedLayout (Decoration DwmStyle s) Circle Window -- | A Circle layout with the xmonad tabbed decoration, default -- theme and default shrinker. -- -- Here you can find a screen shot: -- -- -- http://code.haskell.org/~arossato/xmonadShots/circleSimpleTabbed.png circleSimpleTabbed :: ModifiedLayout (Decoration TabBarDecoration DefaultShrinker) (ModifiedLayout ResizeScreen Circle) Window -- | Similar to circleSimpleTabbed but with the possibility of -- setting a custom shrinker and a custom theme. circleTabbed :: Shrinker s => s -> Theme -> ModifiedLayout (Decoration TabBarDecoration s) (ModifiedLayout ResizeScreen Circle) Window -- | An Accordion layout with the xmonad default decoration, default -- theme and default shrinker. -- -- Here you can find a screen shot: -- -- -- http://code.haskell.org/~arossato/xmonadShots/accordionSimpleDefault.png accordionSimpleDefault :: ModifiedLayout (Decoration DefaultDecoration DefaultShrinker) Accordion Window -- | Similar to accordionSimpleDefault but with the possibility of -- setting a custom shrinker and a custom theme. accordionDefault :: Shrinker s => s -> Theme -> ModifiedLayout (Decoration DefaultDecoration s) Accordion Window -- | An Accordion layout with the xmonad default decoration, default -- theme and default shrinker, but with the possibility of moving windows -- with the mouse, and resize/move them with the keyboard. accordionSimpleDefaultResizable :: ModifiedLayout (Decoration DefaultDecoration DefaultShrinker) (ModifiedLayout MouseResize (ModifiedLayout WindowArranger Accordion)) Window -- | Similar to accordionSimpleDefaultResizable but with the -- possibility of setting a custom shrinker and a custom theme. accordionDefaultResizable :: Shrinker s => s -> Theme -> ModifiedLayout (Decoration DefaultDecoration s) (ModifiedLayout MouseResize (ModifiedLayout WindowArranger Accordion)) Window -- | An Accordion layout with the xmonad simple decoration, default -- theme and default shrinker. -- -- Here you can find a screen shot: -- -- -- http://code.haskell.org/~arossato/xmonadShots/accordionSimpleDeco.png accordionSimpleDeco :: ModifiedLayout (Decoration SimpleDecoration DefaultShrinker) Accordion Window -- | An Accordion layout with the xmonad simple decoration, default -- theme and default shrinker, but with the possibility of moving windows -- with the mouse, and resize/move them with the keyboard. accordionSimpleDecoResizable :: ModifiedLayout (Decoration SimpleDecoration DefaultShrinker) (ModifiedLayout MouseResize (ModifiedLayout WindowArranger Accordion)) Window -- | Similar to accordionSimpleDece but with the possibility of -- setting a custom shrinker and a custom theme. accordionDeco :: Shrinker s => s -> Theme -> ModifiedLayout (Decoration SimpleDecoration s) Accordion Window -- | Similar to accordionSimpleDecoResizable but with the -- possibility of setting a custom shrinker and a custom theme. accordionDecoResizable :: Shrinker s => s -> Theme -> ModifiedLayout (Decoration SimpleDecoration s) (ModifiedLayout MouseResize (ModifiedLayout WindowArranger Accordion)) Window -- | An Accordion layout with the xmonad DwmStyle decoration, -- default theme and default shrinker. -- -- Here you can find a screen shot: -- -- -- http://code.haskell.org/~arossato/xmonadShots/accordionSimpleDwmStyle.png accordionSimpleDwmStyle :: ModifiedLayout (Decoration DwmStyle DefaultShrinker) Accordion Window -- | Similar to accordionSimpleDwmStyle but with the possibility of -- setting a custom shrinker and a custom theme. accordionDwmStyle :: Shrinker s => s -> Theme -> ModifiedLayout (Decoration DwmStyle s) Accordion Window -- | An Accordion layout with the xmonad tabbed decoration, default -- theme and default shrinker. -- -- Here you can find a screen shot: -- -- -- http://code.haskell.org/~arossato/xmonadShots/accordionSimpleTabbed.png accordionSimpleTabbed :: ModifiedLayout (Decoration TabBarDecoration DefaultShrinker) (ModifiedLayout ResizeScreen Accordion) Window -- | Similar to accordionSimpleTabbed but with the possibility of -- setting a custom shrinker and a custom theme. accordionTabbed :: Shrinker s => s -> Theme -> ModifiedLayout (Decoration TabBarDecoration s) (ModifiedLayout ResizeScreen Accordion) Window -- | A Tall layout with the xmonad default decoration, default theme -- and default shrinker. -- -- Here you can find a screen shot: -- -- -- http://code.haskell.org/~arossato/xmonadShots/tallSimpleDefault.png tallSimpleDefault :: ModifiedLayout (Decoration DefaultDecoration DefaultShrinker) Tall Window -- | Similar to tallSimpleDefault but with the possibility of -- setting a custom shrinker and a custom theme. tallDefault :: Shrinker s => s -> Theme -> ModifiedLayout (Decoration DefaultDecoration s) Tall Window -- | A Tall layout with the xmonad default decoration, default theme -- and default shrinker, but with the possibility of moving windows with -- the mouse, and resize/move them with the keyboard. -- -- Here you can find a screen shot: -- -- -- http://code.haskell.org/~arossato/xmonadShots/tallSimpleDefaultResizable.png tallSimpleDefaultResizable :: ModifiedLayout (Decoration DefaultDecoration DefaultShrinker) (ModifiedLayout MouseResize (ModifiedLayout WindowArranger Tall)) Window -- | Similar to tallSimpleDefaultResizable but with the possibility -- of setting a custom shrinker and a custom theme. tallDefaultResizable :: Shrinker s => s -> Theme -> ModifiedLayout (Decoration DefaultDecoration s) (ModifiedLayout MouseResize (ModifiedLayout WindowArranger Tall)) Window -- | A Tall layout with the xmonad simple decoration, default theme -- and default shrinker. -- -- Here you can find a screen shot: -- -- -- http://code.haskell.org/~arossato/xmonadShots/tallSimpleDeco.png tallSimpleDeco :: ModifiedLayout (Decoration SimpleDecoration DefaultShrinker) Tall Window -- | Similar to tallSimpleDece but with the possibility of setting -- a custom shrinker and a custom theme. tallDeco :: Shrinker s => s -> Theme -> ModifiedLayout (Decoration SimpleDecoration s) Tall Window -- | A Tall layout with the xmonad simple decoration, default theme -- and default shrinker, but with the possibility of moving windows with -- the mouse, and resize/move them with the keyboard. -- -- Here you can find a screen shot: -- -- -- http://code.haskell.org/~arossato/xmonadShots/tallSimpleDecoResizable.png tallSimpleDecoResizable :: ModifiedLayout (Decoration SimpleDecoration DefaultShrinker) (ModifiedLayout MouseResize (ModifiedLayout WindowArranger Tall)) Window -- | Similar to tallSimpleDecoResizable but with the possibility of -- setting a custom shrinker and a custom theme. tallDecoResizable :: Shrinker s => s -> Theme -> ModifiedLayout (Decoration SimpleDecoration s) (ModifiedLayout MouseResize (ModifiedLayout WindowArranger Tall)) Window -- | A Tall layout with the xmonad DwmStyle decoration, default -- theme and default shrinker. -- -- Here you can find a screen shot: -- -- -- http://code.haskell.org/~arossato/xmonadShots/tallSimpleDwmStyle.png tallSimpleDwmStyle :: ModifiedLayout (Decoration DwmStyle DefaultShrinker) Tall Window -- | Similar to tallSimpleDwmStyle but with the possibility of -- setting a custom shrinker and a custom theme. tallDwmStyle :: Shrinker s => s -> Theme -> ModifiedLayout (Decoration DwmStyle s) Tall Window -- | A Tall layout with the xmonad tabbed decoration, default theme -- and default shrinker. -- -- Here you can find a screen shot: -- -- -- http://code.haskell.org/~arossato/xmonadShots/tallSimpleTabbed.png tallSimpleTabbed :: ModifiedLayout (Decoration TabBarDecoration DefaultShrinker) (ModifiedLayout ResizeScreen Tall) Window -- | Similar to tallSimpleTabbed but with the possibility of setting -- a custom shrinker and a custom theme. tallTabbed :: Shrinker s => s -> Theme -> ModifiedLayout (Decoration TabBarDecoration s) (ModifiedLayout ResizeScreen Tall) Window -- | A 'Mirror Tall' layout with the xmonad default decoration, default -- theme and default shrinker. -- -- Here you can find a screen shot: -- -- -- http://code.haskell.org/~arossato/xmonadShots/mirrorTallSimpleDefault.png mirrorTallSimpleDefault :: ModifiedLayout (Decoration DefaultDecoration DefaultShrinker) (Mirror Tall) Window -- | Similar to mirrorTallSimpleDefault but with the possibility of -- setting a custom shrinker and a custom theme. mirrorTallDefault :: Shrinker s => s -> Theme -> ModifiedLayout (Decoration DefaultDecoration s) (Mirror Tall) Window -- | A 'Mirror Tall' layout with the xmonad default decoration, default -- theme and default shrinker, but with the possibility of moving windows -- with the mouse, and resize/move them with the keyboard. -- -- Here you can find a screen shot: -- -- -- http://code.haskell.org/~arossato/xmonadShots/mirrorTallSimpleDefaultResizable.png mirrorTallSimpleDefaultResizable :: ModifiedLayout (Decoration DefaultDecoration DefaultShrinker) (ModifiedLayout MouseResize (ModifiedLayout WindowArranger (Mirror Tall))) Window -- | Similar to mirrorTallSimpleDefaultResizable but with the -- possibility of setting a custom shrinker and a custom theme. mirrorTallDefaultResizable :: Shrinker s => s -> Theme -> ModifiedLayout (Decoration DefaultDecoration s) (ModifiedLayout MouseResize (ModifiedLayout WindowArranger (Mirror Tall))) Window -- | A 'Mirror Tall' layout with the xmonad simple decoration, default -- theme and default shrinker. -- -- Here you can find a screen shot: -- -- -- http://code.haskell.org/~arossato/xmonadShots/mirrorTallSimpleDeco.png mirrorTallSimpleDeco :: ModifiedLayout (Decoration SimpleDecoration DefaultShrinker) (Mirror Tall) Window -- | Similar to mirrorTallSimpleDece but with the possibility of -- setting a custom shrinker and a custom theme. mirrorTallDeco :: Shrinker s => s -> Theme -> ModifiedLayout (Decoration SimpleDecoration s) (Mirror Tall) Window -- | A 'Mirror Tall' layout with the xmonad simple decoration, default -- theme and default shrinker, but with the possibility of moving windows -- with the mouse, and resize/move them with the keyboard. -- -- Here you can find a screen shot: -- -- -- http://code.haskell.org/~arossato/xmonadShots/mirrorTallSimpleDecoResizable.png mirrorTallSimpleDecoResizable :: ModifiedLayout (Decoration SimpleDecoration DefaultShrinker) (ModifiedLayout MouseResize (ModifiedLayout WindowArranger (Mirror Tall))) Window -- | Similar to mirrorTallSimpleDecoResizable but with the -- possibility of setting a custom shrinker and a custom theme. mirrorTallDecoResizable :: Shrinker s => s -> Theme -> ModifiedLayout (Decoration SimpleDecoration s) (ModifiedLayout MouseResize (ModifiedLayout WindowArranger (Mirror Tall))) Window -- | A 'Mirror Tall' layout with the xmonad DwmStyle decoration, default -- theme and default shrinker. -- -- Here you can find a screen shot: -- -- -- http://code.haskell.org/~arossato/xmonadShots/mirrorTallSimpleDwmStyle.png mirrorTallSimpleDwmStyle :: ModifiedLayout (Decoration DwmStyle DefaultShrinker) (Mirror Tall) Window -- | Similar to mirrorTallSimpleDwmStyle but with the possibility of -- setting a custom shrinker and a custom theme. mirrorTallDwmStyle :: Shrinker s => s -> Theme -> ModifiedLayout (Decoration DwmStyle s) (Mirror Tall) Window -- | A 'Mirror Tall' layout with the xmonad tabbed decoration, default -- theme and default shrinker. -- -- Here you can find a screen shot: -- -- -- http://code.haskell.org/~arossato/xmonadShots/mirrorTallSimpleTabbed.png mirrorTallSimpleTabbed :: ModifiedLayout (Decoration TabBarDecoration DefaultShrinker) (ModifiedLayout ResizeScreen (Mirror Tall)) Window -- | Similar to mirrorTallSimpleTabbed but with the possibility of -- setting a custom shrinker and a custom theme. mirrorTallTabbed :: Shrinker s => s -> Theme -> ModifiedLayout (Decoration TabBarDecoration s) (ModifiedLayout ResizeScreen (Mirror Tall)) Window -- | A simple floating layout where every window is placed according to the -- window's initial attributes. -- -- Here you can find a screen shot: -- -- -- http://code.haskell.org/~arossato/xmonadShots/floatSimpleSimple.png floatSimpleSimple :: (Show a, Eq a) => ModifiedLayout (Decoration SimpleDecoration DefaultShrinker) (ModifiedLayout MouseResize (ModifiedLayout WindowArranger SimpleFloat)) a floatSimple :: (Show a, Eq a, Shrinker s) => s -> Theme -> ModifiedLayout (Decoration SimpleDecoration s) (ModifiedLayout MouseResize (ModifiedLayout WindowArranger SimpleFloat)) a -- | This version is decorated with the DefaultDecoration style. -- -- Here you can find a screen shot: -- -- -- http://code.haskell.org/~arossato/xmonadShots/floatSimpleDefault.png floatSimpleDefault :: (Show a, Eq a) => ModifiedLayout (Decoration DefaultDecoration DefaultShrinker) (ModifiedLayout MouseResize (ModifiedLayout WindowArranger SimpleFloat)) a -- | Same as floatSimpleDefault, but with the possibility of setting -- a custom shrinker and a custom theme. floatDefault :: (Show a, Eq a, Shrinker s) => s -> Theme -> ModifiedLayout (Decoration DefaultDecoration s) (ModifiedLayout MouseResize (ModifiedLayout WindowArranger SimpleFloat)) a -- | This version is decorated with the DwmStyle. Note that this is -- a keyboard only floating layout. -- -- Here you can find a screen shot: -- -- -- http://code.haskell.org/~arossato/xmonadShots/floatSimpleDwmStyle.png floatSimpleDwmStyle :: (Show a, Eq a) => ModifiedLayout (Decoration DwmStyle DefaultShrinker) (ModifiedLayout MouseResize (ModifiedLayout WindowArranger SimpleFloat)) a -- | Same as floatSimpleDwmStyle, but with the possibility of -- setting a custom shrinker and a custom theme. floatDwmStyle :: (Show a, Eq a, Shrinker s) => s -> Theme -> ModifiedLayout (Decoration DwmStyle s) (ModifiedLayout MouseResize (ModifiedLayout WindowArranger SimpleFloat)) a -- | This version is decorated with the TabbedDecoration style. | -- Mouse dragging is somehow weird. -- -- Here you can find a screen shot: -- -- -- http://code.haskell.org/~arossato/xmonadShots/floatSimpleTabbed.png floatSimpleTabbed :: (Show a, Eq a) => ModifiedLayout (Decoration TabBarDecoration DefaultShrinker) (ModifiedLayout MouseResize (ModifiedLayout WindowArranger SimpleFloat)) a -- | Same as floatSimpleTabbed, but with the possibility of setting -- a custom shrinker and a custom theme. floatTabbed :: (Show a, Eq a, Shrinker s) => s -> Theme -> ModifiedLayout (Decoration TabBarDecoration s) (ModifiedLayout MouseResize (ModifiedLayout WindowArranger SimpleFloat)) a -- | The default value for this type. def :: Default a => a -- | The default xmonad Theme. -- | Deprecated: Use def (from Data.Default, and re-exported by -- XMonad.Layout.Decoration) instead. defaultTheme :: Theme shrinkText :: DefaultShrinker -- | A prompt for appending a single line of text to a file. Useful for -- keeping a file of notes, things to remember for later, and so on--- -- using a keybinding, you can write things down just about as quickly as -- you think of them, so it doesn't have to interrupt whatever else -- you're doing. -- -- Who knows, it might be useful for other purposes as well! module XMonad.Prompt.AppendFile -- | Given an XPrompt configuration and a file path, prompt the user for a -- line of text, and append it to the given file. appendFilePrompt :: XPConfig -> FilePath -> X () data AppendFile instance XMonad.Prompt.XPrompt XMonad.Prompt.AppendFile.AppendFile -- | A module for launch applicationes that receive parameters in the -- command line. The launcher call a prompt to get the parameters. module XMonad.Prompt.AppLauncher -- | Get the user's response to a prompt an launch an application using the -- input as command parameters of the application. launchApp :: XPConfig -> Application -> X () type Application = String data AppPrompt instance XMonad.Prompt.XPrompt XMonad.Prompt.AppLauncher.AppPrompt -- | A module for setting up simple confirmation prompts for keybindings. module XMonad.Prompt.ConfirmPrompt -- | Prompt the user to confirm a given action. We offer no completion and -- simply ask to confirm (ENTER) or cancel (ESCAPE). The actual key -- handling is done by mkXPrompt. confirmPrompt :: XPConfig -> String -> X () -> X () -- | Customized XPrompt prompt that will ask to confirm the given -- string data EnterPrompt instance XMonad.Prompt.XPrompt XMonad.Prompt.ConfirmPrompt.EnterPrompt -- | A directory file executables prompt for XMonad. This might be useful -- if you don't want to have scripts in your PATH environment variable -- (same executable names, different behavior) - otherwise you might want -- to use XMonad.Prompt.Shell instead - but you want to have easy -- access to these executables through the xmonad's prompt. module XMonad.Prompt.DirExec -- | Function dirExecPrompt starts the prompt with list of all -- executable files in directory specified by FilePath. The name -- of the prompt is taken from the last element of the path. If you -- specify root directory - / - as the path, name Root: -- will be used as the name of the prompt instead. The XPConfig -- parameter can be used to customize visuals of the prompt. The runner -- parameter specifies the function used to run the program - see usage -- for more information dirExecPrompt :: XPConfig -> (String -> X ()) -> FilePath -> X () -- | Function dirExecPromptNamed does the same as -- dirExecPrompt except the name of the prompt is specified by -- String parameter. dirExecPromptNamed :: XPConfig -> (String -> X ()) -> FilePath -> String -> X () data DirExec instance XMonad.Prompt.XPrompt XMonad.Prompt.DirExec.DirExec -- | A generic framework for prompting the user for input and passing it -- along to some other action. module XMonad.Prompt.Input -- | Given a prompt configuration and some prompt text, create an X action -- which pops up a prompt waiting for user input, and returns whatever -- they type. Note that the type of the action is X (Maybe -- String), which reflects the fact that the user might cancel the -- prompt (resulting in Nothing), or enter an input string -- s (resulting in Just s). inputPrompt :: XPConfig -> String -> X (Maybe String) -- | The same as inputPrompt, but with a completion function. The -- type ComplFunction is String -> IO [String], as -- defined in XMonad.Prompt. The mkComplFunFromList utility -- function, also defined in XMonad.Prompt, is useful for creating -- such a function from a known list of possibilities. inputPromptWithCompl :: XPConfig -> String -> ComplFunction -> X (Maybe String) -- | A combinator for hooking up an input prompt action to a function which -- can take the result of the input prompt and produce another action. If -- the user cancels the input prompt, the second function will not be -- run. -- -- The astute student of types will note that this is actually a very -- general combinator and has nothing in particular to do with input -- prompts. If you find a more general use for it and want to move it to -- a different module, be my guest. (?+) :: (Monad m) => m (Maybe a) -> (a -> m ()) -> m () data InputPrompt instance XMonad.Prompt.XPrompt XMonad.Prompt.Input.InputPrompt -- | A prompt for sending quick, one-line emails, via the standard GNU -- 'mail' utility (which must be in your $PATH). This module is intended -- mostly as an example of using XMonad.Prompt.Input to build an -- action requiring user input. module XMonad.Prompt.Email -- | Prompt the user for a recipient, subject, and body, and send an email -- via the GNU 'mail' utility. The second argument is a list of addresses -- for autocompletion. emailPrompt :: XPConfig -> [String] -> X () -- | A manual page prompt for XMonad window manager. -- -- TODO -- --
-- ,((modm .|. shiftMask ,xK_b),sendMessage $ SetStruts [minBound .. maxBound] []) ---- -- Hide all gaps: -- --
-- ,((modm .|. controlMask,xK_b),sendMessage $ SetStruts [] [minBound .. maxBound]) ---- -- Show only upper and left gaps: -- --
-- ,((modm .|. controlMask .|. shiftMask,xK_b),sendMessage $ SetStruts [U,L] [minBound .. maxBound]) ---- -- Hide the bottom keeping whatever the other values were: -- --
-- ,((modm .|. controlMask .|. shiftMask,xK_g),sendMessage $ SetStruts [] [D]) --data SetStruts SetStruts :: [Direction2D] -> [Direction2D] -> SetStruts [addedStruts] :: SetStruts -> [Direction2D] -- | These are removed from the currently set struts before -- addedStruts are added. [removedStruts] :: SetStruts -> [Direction2D] -- | Goes through the list of windows and find the gap so that all STRUT -- settings are satisfied. calcGap :: Set Direction2D -> X (Rectangle -> Rectangle) instance GHC.Show.Show XMonad.Hooks.ManageDocks.RectC instance GHC.Classes.Eq XMonad.Hooks.ManageDocks.RectC instance GHC.Show.Show XMonad.Hooks.ManageDocks.SetStruts instance GHC.Read.Read XMonad.Hooks.ManageDocks.SetStruts instance GHC.Show.Show XMonad.Hooks.ManageDocks.ClearGapCache instance GHC.Read.Read XMonad.Hooks.ManageDocks.ClearGapCache instance GHC.Show.Show XMonad.Hooks.ManageDocks.ToggleStruts instance GHC.Read.Read XMonad.Hooks.ManageDocks.ToggleStruts instance GHC.Show.Show (XMonad.Hooks.ManageDocks.AvoidStruts a) instance GHC.Read.Read (XMonad.Hooks.ManageDocks.AvoidStruts a) instance XMonad.Core.Message XMonad.Hooks.ManageDocks.ToggleStruts instance XMonad.Core.Message XMonad.Hooks.ManageDocks.ClearGapCache instance XMonad.Core.Message XMonad.Hooks.ManageDocks.SetStruts instance XMonad.Layout.LayoutModifier.LayoutModifier XMonad.Hooks.ManageDocks.AvoidStruts a -- | xmonad calls the logHook with every internal state update, which is -- useful for (among other things) outputting status information to an -- external status bar program such as xmobar or dzen. DynamicLog -- provides several drop-in logHooks for this purpose, as well as -- flexible tools for specifying your own formatting. module XMonad.Hooks.DynamicLog -- | Run xmonad with a dzen status bar set to some nice defaults. -- --
-- main = xmonad =<< dzen myConfig
--
-- myConfig = def { ... }
--
--
-- The intent is that the above config file should provide a nice status
-- bar with minimal effort.
--
-- If you wish to customize the status bar format at all, you'll have to
-- use the statusBar function instead.
--
-- The binding uses the XMonad.Hooks.ManageDocks module to automatically
-- handle screen placement for dzen, and enables 'mod-b' for toggling the
-- menu bar.
dzen :: LayoutClass l Window => XConfig l -> IO (XConfig (ModifiedLayout AvoidStruts l))
-- | Run xmonad with a xmobar status bar set to some nice defaults.
--
--
-- main = xmonad =<< xmobar myConfig
--
-- myConfig = def { ... }
--
--
-- This works pretty much the same as dzen function above.
xmobar :: LayoutClass l Window => XConfig l -> IO (XConfig (ModifiedLayout AvoidStruts l))
-- | Modifies the given base configuration to launch the given status bar,
-- send status information to that bar, and allocate space on the screen
-- edges for the bar.
statusBar :: LayoutClass l Window => String -> PP -> (XConfig Layout -> (KeyMask, KeySym)) -> XConfig l -> IO (XConfig (ModifiedLayout AvoidStruts l))
-- | An example log hook, which prints status information to stdout in the
-- default format:
--
-- -- 1 2 [3] 4 7 : full : title ---- -- That is, the currently populated workspaces, the current workspace -- layout, and the title of the focused window. -- -- To customize the output format, see dynamicLogWithPP. dynamicLog :: X () -- | Workspace logger with a format designed for Xinerama: -- --
-- [1 9 3] 2 7 ---- -- where 1, 9, and 3 are the workspaces on screens 1, 2 and 3, -- respectively, and 2 and 7 are non-visible, non-empty workspaces. -- -- At the present time, the current layout and window title are not -- shown. The xinerama workspace format shown above can be (mostly) -- replicated using dynamicLogWithPP by setting ppSort to -- getSortByXineramaRule from XMonad.Util.WorkspaceCompare. -- For example, -- --
-- def { ppCurrent = dzenColor "red" "#efebe7"
-- , ppVisible = wrap "[" "]"
-- , ppSort = getSortByXineramaRule
-- }
--
dynamicLogXinerama :: X ()
-- | Write a string to a property on the root window. This property is of
-- type UTF8_STRING. The string must have been processed by encodeString
-- (dynamicLogString does this).
xmonadPropLog' :: String -> String -> X ()
-- | Write a string to the _XMONAD_LOG property on the root window.
xmonadPropLog :: String -> X ()
-- | Format the current status using the supplied pretty-printing format,
-- and write it to stdout.
dynamicLogWithPP :: PP -> X ()
-- | The same as dynamicLogWithPP, except it simply returns the
-- status as a formatted string without actually printing it to stdout,
-- to allow for further processing, or use in some application other than
-- a status bar.
dynamicLogString :: PP -> X String
-- | The PP type allows the user to customize the formatting of
-- status information.
data PP
PP :: (WorkspaceId -> String) -> (WorkspaceId -> String) -> (WorkspaceId -> String) -> (WorkspaceId -> String) -> (WorkspaceId -> String) -> String -> String -> (String -> String) -> (String -> String) -> (String -> String) -> ([String] -> [String]) -> X ([WindowSpace] -> [WindowSpace]) -> [X (Maybe String)] -> (String -> IO ()) -> PP
-- | how to print the tag of the currently focused workspace
[ppCurrent] :: PP -> WorkspaceId -> String
-- | how to print tags of visible but not focused workspaces (xinerama
-- only)
[ppVisible] :: PP -> WorkspaceId -> String
-- | how to print tags of hidden workspaces which contain windows
[ppHidden] :: PP -> WorkspaceId -> String
-- | how to print tags of empty hidden workspaces
[ppHiddenNoWindows] :: PP -> WorkspaceId -> String
-- | format to be applied to tags of urgent workspaces.
[ppUrgent] :: PP -> WorkspaceId -> String
-- | separator to use between different log sections (window name, layout,
-- workspaces)
[ppSep] :: PP -> String
-- | separator to use between workspace tags
[ppWsSep] :: PP -> String
-- | window title format
[ppTitle] :: PP -> String -> String
-- | escape / sanitizes input to ppTitle
[ppTitleSanitize] :: PP -> String -> String
-- | layout name format
[ppLayout] :: PP -> String -> String
-- | how to order the different log sections. By default, this function
-- receives a list with three formatted strings, representing the
-- workspaces, the layout, and the current window title, respectively. If
-- you have specified any extra loggers in ppExtras, their output
-- will also be appended to the list. To get them in the reverse order,
-- you can just use ppOrder = reverse. If you don't want to
-- display the current layout, you could use something like ppOrder =
-- \(ws:_:t:_) -> [ws,t], and so on.
[ppOrder] :: PP -> [String] -> [String]
-- | how to sort the workspaces. See XMonad.Util.WorkspaceCompare
-- for some useful sorts.
[ppSort] :: PP -> X ([WindowSpace] -> [WindowSpace])
-- | loggers for generating extra information such as time and date, system
-- load, battery status, and so on. See XMonad.Util.Loggers for
-- examples, or create your own!
[ppExtras] :: PP -> [X (Maybe String)]
-- | applied to the entire formatted string in order to output it. Can be
-- used to specify an alternative output method (e.g. write to a pipe
-- instead of stdout), and/or to perform some last-minute formatting.
[ppOutput] :: PP -> String -> IO ()
-- | The default pretty printing options, as seen in dynamicLog.
-- | Deprecated: Use def (from Data.Default, and re-exported by
-- XMonad.Hooks.DynamicLog) instead.
defaultPP :: PP
-- | The default value for this type.
def :: Default a => a
-- | Settings to emulate dwm's statusbar, dzen only.
dzenPP :: PP
-- | Some nice xmobar defaults.
xmobarPP :: PP
-- | The options that sjanssen likes to use with xmobar, as an example.
-- Note the use of xmobarColor and the record update on
-- def.
sjanssenPP :: PP
-- | The options that byorgey likes to use with dzen, as another example.
byorgeyPP :: PP
-- | Wrap a string in delimiters, unless it is empty.
wrap :: String -> String -> String -> String
-- | Pad a string with a leading and trailing space.
pad :: String -> String
-- | Trim leading and trailing whitespace from a string.
trim :: String -> String
-- | Limit a string to a certain length, adding "..." if truncated.
shorten :: Int -> String -> String
-- | Use xmobar escape codes to output a string with given foreground and
-- background colors.
xmobarColor :: String -> String -> String -> String
-- | Strip xmobar markup, specifically the fc, icon and
-- action tags and the matching tags like /fc.
xmobarStrip :: String -> String
xmobarStripTags :: [String] -> String -> String
-- | Use dzen escape codes to output a string with given foreground and
-- background colors.
dzenColor :: String -> String -> String -> String
-- | Escape any dzen metacharacters.
dzenEscape :: String -> String
-- | Strip dzen formatting or commands.
dzenStrip :: String -> String
-- | Format the workspace information, given a workspace sorting function,
-- a list of urgent windows, a pretty-printer format, and the current
-- WindowSet.
pprWindowSet :: WorkspaceSort -> [Window] -> PP -> WindowSet -> String
pprWindowSetXinerama :: WindowSet -> String
instance Data.Default.Class.Default XMonad.Hooks.DynamicLog.PP
-- | Utility functions for simulating independent sets of workspaces on
-- each screen (like dwm's workspace model), using internal tags to
-- distinguish workspaces associated with each screen.
module XMonad.Layout.IndependentScreens
type VirtualWorkspace = WorkspaceId
type PhysicalWorkspace = WorkspaceId
workspaces' :: XConfig l -> [VirtualWorkspace]
withScreens :: ScreenId -> [VirtualWorkspace] -> [PhysicalWorkspace]
onCurrentScreen :: (VirtualWorkspace -> WindowSet -> a) -> (PhysicalWorkspace -> WindowSet -> a)
-- | This turns a naive pretty-printer into one that is aware of the
-- independent screens. That is, you can write your pretty printer to
-- behave the way you want on virtual workspaces; this function will
-- convert that pretty-printer into one that first filters out physical
-- workspaces on other screens, then converts all the physical workspaces
-- on this screen to their virtual names.
--
-- For example, if you have handles hLeft and hRight
-- for bars on the left and right screens, respectively, and pp
-- is a pretty-printer function that takes a handle, you could write
--
-- -- logHook = let log screen handle = dynamicLogWithPP . marshallPP screen . pp $ handle -- in log 0 hLeft >> log 1 hRight --marshallPP :: ScreenId -> PP -> PP -- | Take a pretty-printer and turn it into one that only runs when the -- current workspace is one associated with the given screen. The way -- this works is a bit hacky, so beware: the ppOutput field of the -- input will not be invoked if either of the following conditions is -- met: -- --
-- ppFocus s = whenCurrentOn s def
-- { ppOrder = \(_:_:title:_) -> [title]
-- , ppOutput = appendFile ("focus" ++ show s) . (++ "\n")
-- }
--
--
-- Sequence a few of these pretty-printers to get a log hook that keeps
-- each screen's title up-to-date.
whenCurrentOn :: ScreenId -> PP -> PP
-- | In case you don't know statically how many screens there will be, you
-- can call this in main before starting xmonad. For example, part of my
-- config reads
--
--
-- main = do
-- nScreens <- countScreens
-- xmonad $ def {
-- ...
-- workspaces = withScreens nScreens (workspaces def),
-- ...
-- }
--
countScreens :: (MonadIO m, Integral i) => m i
marshall :: ScreenId -> VirtualWorkspace -> PhysicalWorkspace
unmarshall :: PhysicalWorkspace -> (ScreenId, VirtualWorkspace)
unmarshallS :: PhysicalWorkspace -> ScreenId
unmarshallW :: PhysicalWorkspace -> VirtualWorkspace
-- | Convert the tag of the WindowSpace from a
-- VirtualWorkspace to a PhysicalWorkspace.
marshallWindowSpace :: ScreenId -> WindowSpace -> WindowSpace
-- | Convert the tag of the WindowSpace from a
-- PhysicalWorkspace to a VirtualWorkspace.
unmarshallWindowSpace :: WindowSpace -> WindowSpace
-- | If vSort is a function that sorts WindowSpaces with
-- virtual names, then marshallSort s vSort is a function which
-- sorts WindowSpaces with physical names in an analogous way --
-- but keeps only the spaces on screen s.
marshallSort :: ScreenId -> ([WindowSpace] -> [WindowSpace]) -> ([WindowSpace] -> [WindowSpace])
-- | Provides bindings to add and delete links between workspaces. It is
-- aimed at providing useful links between workspaces in a multihead
-- setup. Linked workspaces are view at the same time.
module XMonad.Actions.LinkWorkspaces
switchWS :: (WorkspaceId -> X ()) -> MessageConfig -> WorkspaceId -> X ()
-- | Remove all maps between workspaces
removeAllMatchings :: MessageConfig -> X ()
-- | remove all matching regarding a given workspace
unMatch :: WorkspaceId -> X ()
-- | Toggle the currently displayed workspaces as matching. Starting from
-- the one with focus | a linked list of workspaces is created that will
-- later be iterated by switchToMatching.
toggleLinkWorkspaces :: MessageConfig -> X ()
defaultMessageConf :: MessageConfig
data MessageConfig
MessageConfig :: (ScreenId -> [Char] -> [Char] -> [Char] -> X ()) -> [Char] -> [Char] -> [Char] -> MessageConfig
[messageFunction] :: MessageConfig -> (ScreenId -> [Char] -> [Char] -> [Char] -> X ())
[foreground] :: MessageConfig -> [Char]
[alertedForeground] :: MessageConfig -> [Char]
[background] :: MessageConfig -> [Char]
instance GHC.Show.Show XMonad.Actions.LinkWorkspaces.WorkspaceMap
instance GHC.Read.Read XMonad.Actions.LinkWorkspaces.WorkspaceMap
instance XMonad.Core.ExtensionClass XMonad.Actions.LinkWorkspaces.WorkspaceMap
-- | Turns your workspaces into a more topic oriented system.
module XMonad.Actions.TopicSpace
-- | Topic is just an alias for WorkspaceId
type Topic = WorkspaceId
-- | Dir is just an alias for FilePath but should points to a
-- directory.
type Dir = FilePath
-- | Here is the topic space configuration area.
data TopicConfig
TopicConfig :: Map Topic Dir -> Map Topic (X ()) -> (Topic -> X ()) -> Topic -> Int -> TopicConfig
-- | This mapping associate a directory to each topic.
[topicDirs] :: TopicConfig -> Map Topic Dir
-- | This mapping associate an action to trigger when switching to a given
-- topic which workspace is empty.
[topicActions] :: TopicConfig -> Map Topic (X ())
-- | This is the default topic action.
[defaultTopicAction] :: TopicConfig -> Topic -> X ()
-- | This is the default topic.
[defaultTopic] :: TopicConfig -> Topic
-- | This setups the maximum depth of topic history, usually 10 is a good
-- default since we can bind all of them using numeric keypad.
[maxTopicHistory] :: TopicConfig -> Int
-- | The default value for this type.
def :: Default a => a
-- | Deprecated: Use def (from Data.Default, and re-exported by
-- XMonad.Actions.TopicSpace) instead.
defaultTopicConfig :: TopicConfig
-- | Returns the list of last focused workspaces the empty list otherwise.
getLastFocusedTopics :: X [String]
-- | Given a TopicConfig, the last focused topic, and a predicate
-- that will select topics that one want to keep, this function will set
-- the property of last focused topics.
setLastFocusedTopic :: Topic -> (Topic -> Bool) -> X ()
-- | Reverse the list of "last focused topics"
reverseLastFocusedTopics :: X ()
-- | This function is a variant of pprWindowSet which takes a topic
-- configuration and a pretty-printing record PP. It will show the
-- list of topics sorted historically and highlighting topics with urgent
-- windows.
pprWindowSet :: TopicConfig -> PP -> X String
-- | Given a prompt configuration and a topic configuration, triggers the
-- action associated with the topic given in prompt.
topicActionWithPrompt :: XPConfig -> TopicConfig -> X ()
-- | Given a configuration and a topic, triggers the action associated with
-- the given topic.
topicAction :: TopicConfig -> Topic -> X ()
-- | Trigger the action associated with the current topic.
currentTopicAction :: TopicConfig -> X ()
-- | Switch to the given topic.
switchTopic :: TopicConfig -> Topic -> X ()
-- | Switch to the Nth last focused topic or failback to the
-- defaultTopic.
switchNthLastFocused :: TopicConfig -> Int -> X ()
-- | Shift the focused window to the Nth last focused topic, or fallback to
-- doing nothing.
shiftNthLastFocused :: Int -> X ()
-- | Returns the directory associated with current topic returns the empty
-- string otherwise.
currentTopicDir :: TopicConfig -> X String
-- | Check the given topic configuration for duplicates topics or undefined
-- topics.
checkTopicConfig :: [Topic] -> TopicConfig -> IO ()
-- | An alias for flip replicateM_
(>*>) :: Monad m => m a -> Int -> m ()
instance GHC.Show.Show XMonad.Actions.TopicSpace.PrevTopics
instance GHC.Read.Read XMonad.Actions.TopicSpace.PrevTopics
instance Data.Default.Class.Default XMonad.Actions.TopicSpace.TopicConfig
instance XMonad.Core.ExtensionClass XMonad.Actions.TopicSpace.PrevTopics
-- | Manage per-screen status bars.
module XMonad.Hooks.DynamicBars
type DynamicStatusBar = ScreenId -> IO Handle
type DynamicStatusBarCleanup = IO ()
dynStatusBarStartup :: DynamicStatusBar -> DynamicStatusBarCleanup -> X ()
dynStatusBarEventHook :: DynamicStatusBar -> DynamicStatusBarCleanup -> Event -> X All
multiPP :: PP -> PP -> X ()
instance XMonad.Core.ExtensionClass XMonad.Hooks.DynamicBars.DynStatusBarInfo
-- | A collection of simple logger functions and formatting utilities which
-- can be used in the ppExtras field of a pretty-printing status
-- logger format. See XMonad.Hooks.DynamicLog for more
-- information.
module XMonad.Util.Loggers
-- | Logger is just a convenient synonym for X (Maybe
-- String).
type Logger = X (Maybe String)
-- | Get the current volume with aumix.
-- http://jpj.net/~trevor/aumix.html
aumixVolume :: Logger
-- | Get the battery status (percent charge and charging/discharging
-- status). This is an ugly hack and may not work for some people. At
-- some point it would be nice to make this more general/have fewer
-- dependencies (assumes /usr/bin/acpi and sed are
-- installed.)
battery :: Logger
-- | Get the current date and time, and format them via the given format
-- string. The format used is the same as that used by the C library
-- function strftime; for example, date "%a %b %d" might display
-- something like Tue Feb 19. For more information see something
-- like
-- http://www.cplusplus.com/reference/clibrary/ctime/strftime.html.
date :: String -> Logger
-- | Get the load average. This assumes that you have a utility called
-- /usr/bin/uptime and that you have sed installed;
-- these are fairly common on GNU/Linux systems but it would be nice to
-- make this more general.
loadAvg :: Logger
-- | Get a count of new mails in a maildir.
maildirNew :: FilePath -> Logger
-- | Get a count of unread mails in a maildir. For maildir format details,
-- to write loggers for other classes of mail, see
-- http://cr.yp.to/proto/maildir.html and logFileCount.
maildirUnread :: FilePath -> Logger
-- | Create a Logger from an arbitrary shell command.
logCmd :: String -> Logger
-- | Get a count of filtered files in a directory. See maildirUnread
-- and maildirNew source for usage examples.
logFileCount :: FilePath -> (String -> Bool) -> Logger
-- | Get the name of the current workspace.
logCurrent :: Logger
-- | Get the name of the current layout.
logLayout :: Logger
-- | Get the title (name) of the focused window.
logTitle :: Logger
-- | Use a string formatting function to edit a Logger string. For
-- example, to create a tag function to prefix or label loggers, as in
-- 'tag: output', use:
--
-- -- tagL l = onLogger $ wrap (l ++ ": ") "" -- -- tagL "bat" battery -- tagL "load" loadAvg ---- -- If you already have a (String -> String) function you want to apply -- to a logger: -- --
-- revL = onLogger trim ---- -- See formatting utility source code for more onLogger usage -- examples. onLogger :: (String -> String) -> Logger -> Logger -- | Wrap a logger's output in delimiters, unless it is X -- (Nothing) or X (Just ""). Some examples: -- --
-- wrapL " | " " | " (date "%a %d %b") -- ' | Tue 19 Feb | ' -- -- wrapL "bat: " "" battery -- ' bat: battery_logger_output' --wrapL :: String -> String -> Logger -> Logger -- | Make a logger's output constant width by padding with the given -- string, even if the logger is X (Nothing) or -- X (Just ""). Useful to reduce visual noise as a title logger -- shrinks and grows, to use a fixed width for a logger that sometimes -- becomes Nothing, or even to create fancy spacers or character based -- art effects. -- -- It fills missing logger output with a repeated character like ".", ":" -- or pattern, like " -.-". The cycling padding string is reversed on the -- left of the logger output. This is mainly useful with AlignCenter. fixedWidthL :: Align -> String -> Int -> Logger -> Logger -- | Create a "spacer" logger, e.g. logSp 3 -- loggerizes ' '. For -- more complex "spacers", use fixedWidthL with return -- Nothing. logSp :: Int -> Logger -- | Pad a logger's output with a leading and trailing space, unless it is -- X (Nothing) or X (Just ""). padL :: Logger -> Logger -- | Limit a logger's length, adding "..." if truncated. shortenL :: Int -> Logger -> Logger -- | Color a logger's output with dzen foreground and background colors. -- --
-- dzenColorL "green" "#2A4C3F" battery --dzenColorL :: String -> String -> Logger -> Logger -- | Color a logger's output with xmobar foreground and background colors. -- --
-- xmobarColorL "#6A5ACD" "gray6" loadAverage --xmobarColorL :: String -> String -> Logger -> Logger -- | An infix synonym for fmap. -- --
-- >>> show <$> Nothing -- Nothing -- -- >>> show <$> Just 3 -- Just "3" ---- -- Convert from an Either Int Int to -- an Either Int String using -- show: -- --
-- >>> show <$> Left 17 -- Left 17 -- -- >>> show <$> Right 17 -- Right "17" ---- -- Double each element of a list: -- --
-- >>> (*2) <$> [1,2,3] -- [2,4,6] ---- -- Apply even to the second element of a pair: -- --
-- >>> even <$> (2,2) -- (2,True) --(<$>) :: Functor f => (a -> b) -> f a -> f b -- | Named scratchpads that support several arbitrary applications at the -- same time. module XMonad.Util.NamedScratchpad -- | Single named scratchpad configuration data NamedScratchpad NS :: String -> String -> Query Bool -> ManageHook -> NamedScratchpad -- | Scratchpad name [name] :: NamedScratchpad -> String -- | Command used to run application [cmd] :: NamedScratchpad -> String -- | Query to find already running application [query] :: NamedScratchpad -> Query Bool -- | Manage hook called for application window, use it to define the -- placement. See nonFloating, defaultFloating and -- customFloating [hook] :: NamedScratchpad -> ManageHook -- | Manage hook that makes the window non-floating nonFloating :: ManageHook -- | Manage hook that makes the window floating with the default placement defaultFloating :: ManageHook -- | Manage hook that makes the window floating with custom placement customFloating :: RationalRect -> ManageHook -- | Named scratchpads configuration type NamedScratchpads = [NamedScratchpad] -- | Action to pop up specified named scratchpad namedScratchpadAction :: NamedScratchpads -> String -> X () allNamedScratchpadAction :: NamedScratchpads -> String -> X () -- | Manage hook to use with named scratchpads namedScratchpadManageHook :: NamedScratchpads -> ManageHook -- | Transforms a workspace list containing the NSP workspace into one that -- doesn't contain it. Intended for use with logHooks. namedScratchpadFilterOutWorkspace :: [WindowSpace] -> [WindowSpace] -- | Transforms a pretty-printer into one not displaying the NSP workspace. -- -- A simple use could be: -- --
-- logHook = dynamicLogWithPP . namedScratchpadFilterOutWorkspace $ def ---- -- Here is another example, when using -- XMonad.Layout.IndependentScreens. If you have handles -- hLeft and hRight for bars on the left and right -- screens, respectively, and pp is a pretty-printer function -- that takes a handle, you could write -- --
-- logHook = let log screen handle = dynamicLogWithPP . namedScratchpadFilterOutWorkspacePP . marshallPP screen . pp $ handle -- in log 0 hLeft >> log 1 hRight --namedScratchpadFilterOutWorkspacePP :: PP -> PP -- | Very handy hotkey-launched floating terminal window. module XMonad.Util.Scratchpad -- | Action to pop up the terminal, for the user to bind to a custom key. scratchpadSpawnAction :: XConfig l -> X () -- | Action to pop up the terminal, with a directly specified terminal. scratchpadSpawnActionTerminal :: String -> X () -- | Action to pop up any program with the user specifying how to set its -- resource to "scratchpad". For example, with gnome-terminal: -- --
-- scratchpadSpawnActionCustom "gnome-terminal --disable-factory --name scratchpad" --scratchpadSpawnActionCustom :: String -> X () -- | The ManageHook, with the default rectangle: Half the screen wide, a -- quarter of the screen tall, centered. scratchpadManageHookDefault :: ManageHook -- | The ManageHook, with a user-specified StackSet.RationalRect, e.g., for -- a terminal 4/10 of the screen width from the left, half the screen -- height from the top, and 6/10 of the screen width by 3/10 the screen -- height, use: -- --
-- scratchpadManageHook (W.RationalRect 0.4 0.5 0.6 0.3) --scratchpadManageHook :: RationalRect -> ManageHook -- | Transforms a workspace list containing the SP workspace into one that -- doesn't contain it. Intended for use with logHooks. scratchpadFilterOutWorkspace :: [WindowSpace] -> [WindowSpace] -- | This module contains two hooks for the PositionStore (see -- XMonad.Util.PositionStore) - a ManageHook and an EventHook. -- -- The ManageHook can be used to fill the PositionStore with position and -- size information about new windows. The advantage of using this hook -- is, that the information is recorded independent of the currently -- active layout. So the floating shape of the window can later be -- restored even if it was opened in a tiled layout initially. -- -- For windows, that do not request a particular position, a random -- position will be assigned. This prevents windows from piling up -- exactly on top of each other. -- -- The EventHook makes sure that windows are deleted from the -- PositionStore when they are closed. module XMonad.Hooks.PositionStoreHooks positionStoreManageHook :: Maybe Theme -> ManageHook positionStoreEventHook :: Event -> X All -- | This module provides a config suitable for use with a desktop -- environment such as KDE or GNOME. module XMonad.Config.Desktop desktopConfig :: XConfig (ModifiedLayout AvoidStruts (Choose Tall (Choose (Mirror Tall) Full))) desktopLayoutModifiers :: LayoutClass l a => l a -> ModifiedLayout AvoidStruts l a -- | This module provides a config suitable for use with the GNOME desktop -- environment. module XMonad.Config.Gnome gnomeConfig :: XConfig (ModifiedLayout AvoidStruts (Choose Tall (Choose (Mirror Tall) Full))) -- | Launch the "Run Application" dialog. gnome-panel must be running for -- this to work. gnomeRun :: X () -- | Register xmonad with gnome. 'dbus-send' must be in the $PATH with -- which xmonad is started. -- -- This action reduces a delay on startup only only if you have -- configured gnome-session>=2.26: to start xmonad with a command as -- such: -- --
-- gconftool-2 -s /desktop/gnome/session/required_components/windowmanager xmonad --type string --gnomeRegister :: MonadIO m => m () -- | This module provides a config suitable for use with the KDE desktop -- environment. module XMonad.Config.Kde kdeConfig :: XConfig (ModifiedLayout AvoidStruts (Choose Tall (Choose (Mirror Tall) Full))) kde4Config :: XConfig (ModifiedLayout AvoidStruts (Choose Tall (Choose (Mirror Tall) Full))) -- | This module provides a config suitable for use with the MATE desktop -- environment. module XMonad.Config.Mate mateConfig :: XConfig (ModifiedLayout AvoidStruts (Choose Tall (Choose (Mirror Tall) Full))) -- | Launch the "Run Application" dialog. mate-panel must be running for -- this to work. mateRun :: X () -- | Register xmonad with mate. 'dbus-send' must be in the $PATH with which -- xmonad is started. -- -- This action reduces a delay on startup only if you have configured -- mate-session to start xmonad with a command such as (check local -- documentation): -- --
-- dconf write /org/mate/desktop/session/required_components/windowmanager "'xmonad'" ---- -- (the extra quotes are required by dconf) mateRegister :: MonadIO m => m () -- | This module provides a config suitable for use with the Xfce desktop -- environment. module XMonad.Config.Xfce xfceConfig :: XConfig (ModifiedLayout AvoidStruts (Choose Tall (Choose (Mirror Tall) Full))) module XMonad.Config.Dmwit outputOf :: String -> IO String geomMean :: Floating a => [a] -> a arithMean :: Floating a => [a] -> a namedNumbers :: [Char] -> String -> [[Char]] splitColon :: [Char] -> [[Char]] parse :: (Floating a, Read a) => String -> a modVolume :: String -> Integer -> IO Double centerMouse :: X () statusBarMouse :: X () withScreen :: ScreenId -> (WorkspaceId -> WindowSet -> WindowSet) -> X () makeLauncher :: [Char] -> [Char] -> [Char] -> [Char] -> [Char] launcher :: [Char] termLauncher :: [Char] viewShift :: (Eq i, Eq s, Ord a) => i -> StackSet i l a s sd -> StackSet i l a s sd floatAll :: [String] -> Query (Endo WindowSet) sinkFocus :: Ord a => StackSet i l a s sd -> StackSet i l a s sd showMod :: String -> Integer -> X () volumeDzen :: String -> X () altMask :: KeyMask bright :: [Char] dark :: [Char] fullscreen43on169 :: RationalRect fullscreenMPlayer :: Query (Endo (StackSet PhysicalWorkspace (Layout Window) Window ScreenId ScreenDetail)) operationOn :: (Eq s, Ord a) => (a -> StackSet PhysicalWorkspace l a s sd -> StackSet PhysicalWorkspace l a s sd) -> ScreenId -> VirtualWorkspace -> a -> Query (Endo (StackSet PhysicalWorkspace l a s sd)) viewFullOn :: (Eq s, Ord a) => ScreenId -> VirtualWorkspace -> a -> Query (Endo (StackSet PhysicalWorkspace l a s sd)) centerWineOn :: (Eq s, Ord a) => ScreenId -> VirtualWorkspace -> a -> Query (Endo (StackSet PhysicalWorkspace l a s sd)) class Show a => PPrint a where pprint _ = show pprint :: PPrint a => Int -> a -> String data PPrintable P :: a -> PPrintable record :: String -> Int -> [(String, PPrintable)] -> String dmwitConfig :: ScreenId -> XConfig (ModifiedLayout Magnifier (Choose (ModifiedLayout AvoidStruts Grid) (ModifiedLayout WithBorder Full))) main :: IO () keyBindings :: XConfig Layout -> Map (KeyMask, KeySym) (X ()) atSchool :: MonadIO m => r -> r -> m r anyMask :: [((KeyMask, t1), t)] -> [((KeyMask, t1), t)] pipeName :: Show a => [Char] -> a -> [Char] xmobarCommand :: ScreenId -> String allPPs :: ScreenId -> X () color :: String -> String -> String ppFocus :: ScreenId -> PP ppWorkspaces :: ScreenId -> PP instance GHC.Show.Show XMonad.Config.Dmwit.PPrintable instance XMonad.Config.Dmwit.PPrint XMonad.Config.Dmwit.PPrintable instance XMonad.Config.Dmwit.PPrint a => XMonad.Config.Dmwit.PPrint (GHC.Base.Maybe a) instance XMonad.Config.Dmwit.PPrint a => XMonad.Config.Dmwit.PPrint [a] instance XMonad.Config.Dmwit.PPrint Graphics.X11.Xlib.Types.Rectangle instance XMonad.Config.Dmwit.PPrint a => XMonad.Config.Dmwit.PPrint (XMonad.StackSet.Stack a) instance (XMonad.Config.Dmwit.PPrint i, XMonad.Config.Dmwit.PPrint l, XMonad.Config.Dmwit.PPrint a) => XMonad.Config.Dmwit.PPrint (XMonad.StackSet.Workspace i l a) instance XMonad.Config.Dmwit.PPrint XMonad.Core.ScreenDetail instance (XMonad.Config.Dmwit.PPrint i, XMonad.Config.Dmwit.PPrint l, XMonad.Config.Dmwit.PPrint a, XMonad.Config.Dmwit.PPrint sid, XMonad.Config.Dmwit.PPrint sd) => XMonad.Config.Dmwit.PPrint (XMonad.StackSet.Screen i l a sid sd) instance (XMonad.Config.Dmwit.PPrint i, XMonad.Config.Dmwit.PPrint l, XMonad.Config.Dmwit.PPrint a, XMonad.Config.Dmwit.PPrint sid, XMonad.Config.Dmwit.PPrint sd) => XMonad.Config.Dmwit.PPrint (XMonad.StackSet.StackSet i l a sid sd) instance XMonad.Config.Dmwit.PPrint (XMonad.Core.Layout a) instance XMonad.Config.Dmwit.PPrint GHC.Types.Int instance XMonad.Config.Dmwit.PPrint Graphics.X11.Xlib.Types.Screen instance XMonad.Config.Dmwit.PPrint GHC.Integer.Type.Integer instance XMonad.Config.Dmwit.PPrint Graphics.X11.Xlib.Types.Position instance XMonad.Config.Dmwit.PPrint Graphics.X11.Xlib.Types.Dimension instance XMonad.Config.Dmwit.PPrint GHC.Types.Char instance XMonad.Config.Dmwit.PPrint GHC.Word.Word64 instance XMonad.Config.Dmwit.PPrint XMonad.Core.ScreenId instance (GHC.Show.Show a, GHC.Show.Show b) => XMonad.Config.Dmwit.PPrint (Data.Map.Base.Map a b) -- | Support for simple mouse gestures. module XMonad.Actions.MouseGestures -- | Two-dimensional directions: data Direction2D -- | Up U :: Direction2D -- | Down D :: Direction2D -- | Right R :: Direction2D -- | Left L :: Direction2D -- | mouseGestureH moveHook endHook is a mouse button event -- handler. It collects mouse movements, calling moveHook for -- each update; when the button is released, it calls endHook. mouseGestureH :: (Direction2D -> X ()) -> X () -> X () -- | A utility function on top of mouseGestureH. It uses a -- Map to look up the mouse gesture, then executes the -- corresponding action (if any). mouseGesture :: Map [Direction2D] (Window -> X ()) -> Window -> X () -- | A callback generator for mouseGestureH. mkCollect -- returns two callback functions for passing to mouseGestureH. -- The move hook will collect mouse movements (and return the current -- gesture as a list); the end hook will return a list of the completed -- gesture, which you can access with >>=. mkCollect :: (MonadIO m, MonadIO m') => m (Direction2D -> m' [Direction2D], m' [Direction2D]) -- | Navigation2D is an xmonad extension that allows easy directional -- navigation of windows and screens (in a multi-monitor setup). module XMonad.Actions.Navigation2D -- | Convenience function for enabling Navigation2D with typical -- keybindings. Takes a Navigation2DConfig, an (up, left, down, right) -- tuple, a mapping from modifier key to action, and a bool to indicate -- if wrapping should occur, and returns a function from XConfig to -- XConfig. Example: -- --
-- navigation2D def (xK_w, xK_a, xK_s, xK_d) [(mod4Mask, windowGo), (mod4Mask .|. shiftMask, windowSwap)] False myConfig --navigation2D :: Navigation2DConfig -> (KeySym, KeySym, KeySym, KeySym) -> [(ButtonMask, Direction2D -> Bool -> X ())] -> Bool -> XConfig l -> XConfig l -- | Convenience function for enabling Navigation2D with typical -- keybindings, using the syntax defined in mkKeymap. Takes a -- Navigation2DConfig, an (up, left, down, right) tuple, a mapping from -- key prefix to action, and a bool to indicate if wrapping should occur, -- and returns a function from XConfig to XConfig. Example: -- --
-- navigation2DP def ("w", "a", "s", "d") [("M-", windowGo), ("M-S-", windowSwap)] False myConfig
--
navigation2DP :: Navigation2DConfig -> (String, String, String, String) -> [(String, Direction2D -> Bool -> X ())] -> Bool -> XConfig l -> XConfig l
-- | Convenience function for adding keybindings. Takes an (up, left, down,
-- right) tuple, a mapping from key prefix to action, and a bool to
-- indicate if wrapping should occur, and returns a function from XConfig
-- to XConfig. Example:
--
-- -- additionalNav2DKeys (xK_w, xK_a, xK_s, xK_d) [(mod4Mask, windowGo), (mod4Mask .|. shiftMask, windowSwap)] False myConfig --additionalNav2DKeys :: (KeySym, KeySym, KeySym, KeySym) -> [(ButtonMask, Direction2D -> Bool -> X ())] -> Bool -> XConfig l -> XConfig l -- | Convenience function for adding keybindings, using the syntax defined -- in mkKeymap. Takes an (up, left, down, right) tuple, a mapping -- from key prefix to action, and a bool to indicate if wrapping should -- occur, and returns a function from XConfig to XConfig. Example: -- --
-- additionalNav2DKeysP def ("w", "a", "s", "d") [("M-", windowGo), ("M-S-", windowSwap)] False myConfig
--
additionalNav2DKeysP :: (String, String, String, String) -> [(String, Direction2D -> Bool -> X ())] -> Bool -> XConfig l -> XConfig l
-- | Modifies the xmonad configuration to store the Navigation2D
-- configuration
withNavigation2DConfig :: Navigation2DConfig -> XConfig a -> XConfig a
-- | Stores the configuration of directional navigation. The Default
-- instance uses line navigation for the tiled layer and for navigation
-- between screens, and center navigation for the float layer. No custom
-- navigation strategies or rectangles for unmapped windows are defined
-- for individual layouts.
data Navigation2DConfig
Navigation2DConfig :: Navigation2D -> Navigation2D -> Navigation2D -> [(String, Navigation2D)] -> [(String, Screen -> Window -> X (Maybe Rectangle))] -> Navigation2DConfig
-- | default navigation strategy for the tiled layer
[defaultTiledNavigation] :: Navigation2DConfig -> Navigation2D
-- | navigation strategy for the float layer
[floatNavigation] :: Navigation2DConfig -> Navigation2D
-- | strategy for navigation between screens
[screenNavigation] :: Navigation2DConfig -> Navigation2D
-- | association list of customized navigation strategies for different
-- layouts in the tiled layer. Each pair is of the form ("layout
-- description", navigation strategy). If there is no pair in this list
-- whose first component is the name of the current layout, the
-- defaultTiledNavigation strategy is used.
[layoutNavigation] :: Navigation2DConfig -> [(String, Navigation2D)]
-- | list associating functions to calculate rectangles for unmapped
-- windows with layouts to which they are to be applied. Each pair in
-- this list is of the form ("layout description", function), where the
-- function calculates a rectangle for a given unmapped window from the
-- screen it is on and its window ID. See #Finer_Points for how to
-- use this.
[unmappedWindowRect] :: Navigation2DConfig -> [(String, Screen -> Window -> X (Maybe Rectangle))]
-- | The default value for this type.
def :: Default a => a
-- | Deprecated: Use def (from Data.Default, and re-exported from
-- XMonad.Actions.Navigation2D) instead.
defaultNavigation2DConfig :: Navigation2DConfig
-- | Encapsulates the navigation strategy
data Navigation2D
-- | Line navigation. To illustrate this navigation strategy, consider
-- navigating to the left from the current window. In this case, we draw
-- a horizontal line through the center of the current window and
-- consider all windows that intersect this horizontal line and whose
-- right boundaries are to the left of the left boundary of the current
-- window. From among these windows, we choose the one with the rightmost
-- right boundary.
lineNavigation :: Navigation2D
-- | Center navigation. Again, consider navigating to the left. Then we
-- consider the cone bounded by the two rays shot at 45-degree angles in
-- north-west and south-west direction from the center of the current
-- window. A window is a candidate to receive the focus if its center
-- lies in this cone. We choose the window whose center has minimum
-- L1-distance from the current window center. The tie breaking strategy
-- for windows with the same distance is a bit complicated (see
-- #Technical_Discussion) but ensures that all windows can be
-- reached and that windows with the same center are traversed in their
-- order in the window stack, that is, in the order focusUp and
-- focusDown would traverse them.
centerNavigation :: Navigation2D
-- | Maps each window to a fullscreen rect. This may not be the same
-- rectangle the window maps to under the Full layout or a similar layout
-- if the layout respects statusbar struts. In such cases, it may be
-- better to use singleWindowRect.
fullScreenRect :: Screen -> Window -> X (Maybe Rectangle)
-- | Maps each window to the rectangle it would receive if it was the only
-- window in the layout. Useful, for example, for determining the default
-- rectangle for unmapped windows in a Full layout that respects
-- statusbar struts.
singleWindowRect :: Screen -> Window -> X (Maybe Rectangle)
-- | Switches focus to the closest window in the other layer (floating if
-- the current window is tiled, tiled if the current window is floating).
-- Closest means that the L1-distance between the centers of the windows
-- is minimized.
switchLayer :: X ()
-- | Moves the focus to the next window in the given direction and in the
-- same layer as the current window. The second argument indicates
-- whether navigation should wrap around (e.g., from the left edge of the
-- leftmost screen to the right edge of the rightmost screen).
windowGo :: Direction2D -> Bool -> X ()
-- | Swaps the current window with the next window in the given direction
-- and in the same layer as the current window. (In the floating layer,
-- all that changes for the two windows is their stacking order if
-- they're on the same screen. If they're on different screens, each
-- window is moved to the other window's screen but retains its position
-- and size relative to the screen.) The second argument indicates
-- wrapping (see windowGo).
windowSwap :: Direction2D -> Bool -> X ()
-- | Moves the current window to the next screen in the given direction.
-- The second argument indicates wrapping (see windowGo).
windowToScreen :: Direction2D -> Bool -> X ()
-- | Moves the focus to the next screen in the given direction. The second
-- argument indicates wrapping (see windowGo).
screenGo :: Direction2D -> Bool -> X ()
-- | Swaps the workspace on the current screen with the workspace on the
-- screen in the given direction. The second argument indicates wrapping
-- (see windowGo).
screenSwap :: Direction2D -> Bool -> X ()
-- | Two-dimensional directions:
data Direction2D
-- | Up
U :: Direction2D
-- | Down
D :: Direction2D
-- | Right
R :: Direction2D
-- | Left
L :: Direction2D
instance GHC.Classes.Eq XMonad.Actions.Navigation2D.Navigation2D
instance GHC.Classes.Ord XMonad.Actions.Navigation2D.Navigation2D
instance XMonad.Core.ExtensionClass XMonad.Actions.Navigation2D.Navigation2DConfig
instance Data.Default.Class.Default XMonad.Actions.Navigation2D.Navigation2DConfig
-- | License : BSD3-style (see LICENSE) Stability : unstable Portability :
-- unportable
--
-- This is a rewrite of XMonad.Layout.WindowNavigation.
-- WindowNavigation lets you assign keys to move up/down/left/right,
-- based on actual cartesian window coordinates, rather than just going
-- j/k on the stack.
--
-- This module is experimental. You'll have better luck with the
-- original.
--
-- This module differs from the other in a few ways:
--
--
-- import XMonad
-- import XMonad.Layout.Tabbed
-- main = xmonad def { layoutHook = simpleTabbed }
--
simpleTabbed :: ModifiedLayout (Decoration TabbedDecoration DefaultShrinker) Simplest Window
-- | A layout decorated with tabs and the possibility to set a custom
-- shrinker and theme.
tabbed :: (Eq a, Shrinker s) => s -> Theme -> ModifiedLayout (Decoration TabbedDecoration s) Simplest a
-- | A layout modifier that uses the provided shrinker and theme to add
-- tabs to any layout.
addTabs :: (Eq a, LayoutClass l a, Shrinker s) => s -> Theme -> l a -> ModifiedLayout (Decoration TabbedDecoration s) l a
simpleTabbedAlways :: ModifiedLayout (Decoration TabbedDecoration DefaultShrinker) Simplest Window
tabbedAlways :: (Eq a, Shrinker s) => s -> Theme -> ModifiedLayout (Decoration TabbedDecoration s) Simplest a
addTabsAlways :: (Eq a, LayoutClass l a, Shrinker s) => s -> Theme -> l a -> ModifiedLayout (Decoration TabbedDecoration s) l a
-- | A bottom-tabbed layout with the default xmonad Theme.
simpleTabbedBottom :: ModifiedLayout (Decoration TabbedDecoration DefaultShrinker) Simplest Window
-- | A layout decorated with tabs at the bottom and the possibility to set
-- a custom shrinker and theme.
tabbedBottom :: (Eq a, Shrinker s) => s -> Theme -> ModifiedLayout (Decoration TabbedDecoration s) Simplest a
-- | A layout modifier that uses the provided shrinker and theme to add
-- tabs to the bottom of any layout.
addTabsBottom :: (Eq a, LayoutClass l a, Shrinker s) => s -> Theme -> l a -> ModifiedLayout (Decoration TabbedDecoration s) l a
-- | A side-tabbed layout with the default xmonad Theme.
simpleTabbedLeft :: ModifiedLayout (Decoration TabbedDecoration DefaultShrinker) Simplest Window
-- | A layout decorated with tabs and the possibility to set a custom
-- shrinker and theme.
tabbedLeft :: (Eq a, Shrinker s) => s -> Theme -> ModifiedLayout (Decoration TabbedDecoration s) Simplest a
-- | A layout modifier that uses the provided shrinker and theme to add
-- tabs to the side of any layout.
addTabsLeft :: (Eq a, LayoutClass l a, Shrinker s) => s -> Theme -> l a -> ModifiedLayout (Decoration TabbedDecoration s) l a
-- | A side-tabbed layout with the default xmonad Theme.
simpleTabbedRight :: ModifiedLayout (Decoration TabbedDecoration DefaultShrinker) Simplest Window
-- | A layout decorated with tabs and the possibility to set a custom
-- shrinker and theme.
tabbedRight :: (Eq a, Shrinker s) => s -> Theme -> ModifiedLayout (Decoration TabbedDecoration s) Simplest a
-- | A layout modifier that uses the provided shrinker and theme to add
-- tabs to the side of any layout.
addTabsRight :: (Eq a, LayoutClass l a, Shrinker s) => s -> Theme -> l a -> ModifiedLayout (Decoration TabbedDecoration s) l a
-- | A bottom-tabbed layout with the default xmonad Theme.
simpleTabbedBottomAlways :: ModifiedLayout (Decoration TabbedDecoration DefaultShrinker) Simplest Window
tabbedBottomAlways :: (Eq a, Shrinker s) => s -> Theme -> ModifiedLayout (Decoration TabbedDecoration s) Simplest a
addTabsBottomAlways :: (Eq a, LayoutClass l a, Shrinker s) => s -> Theme -> l a -> ModifiedLayout (Decoration TabbedDecoration s) l a
-- | A side-tabbed layout with the default xmonad Theme.
simpleTabbedLeftAlways :: ModifiedLayout (Decoration TabbedDecoration DefaultShrinker) Simplest Window
-- | A layout decorated with tabs and the possibility to set a custom
-- shrinker and theme.
tabbedLeftAlways :: (Eq a, Shrinker s) => s -> Theme -> ModifiedLayout (Decoration TabbedDecoration s) Simplest a
addTabsLeftAlways :: (Eq a, LayoutClass l a, Shrinker s) => s -> Theme -> l a -> ModifiedLayout (Decoration TabbedDecoration s) l a
-- | A side-tabbed layout with the default xmonad Theme.
simpleTabbedRightAlways :: ModifiedLayout (Decoration TabbedDecoration DefaultShrinker) Simplest Window
-- | A layout decorated with tabs and the possibility to set a custom
-- shrinker and theme.
tabbedRightAlways :: (Eq a, Shrinker s) => s -> Theme -> ModifiedLayout (Decoration TabbedDecoration s) Simplest a
addTabsRightAlways :: (Eq a, LayoutClass l a, Shrinker s) => s -> Theme -> l a -> ModifiedLayout (Decoration TabbedDecoration s) l a
-- | A Theme is a record of colors, font etc., to customize a
-- DecorationStyle.
--
-- For a collection of Themes see XMonad.Util.Themes
data Theme
Theme :: String -> String -> String -> String -> String -> String -> String -> String -> String -> String -> Dimension -> Dimension -> [(String, Align)] -> [([[Bool]], Placement)] -> Theme
-- | Color of the active window
[activeColor] :: Theme -> String
-- | Color of the inactive window
[inactiveColor] :: Theme -> String
-- | Color of the urgent window
[urgentColor] :: Theme -> String
-- | Color of the border of the active window
[activeBorderColor] :: Theme -> String
-- | Color of the border of the inactive window
[inactiveBorderColor] :: Theme -> String
-- | Color of the border of the urgent window
[urgentBorderColor] :: Theme -> String
-- | Color of the text of the active window
[activeTextColor] :: Theme -> String
-- | Color of the text of the inactive window
[inactiveTextColor] :: Theme -> String
-- | Color of the text of the urgent window
[urgentTextColor] :: Theme -> String
-- | Font name
[fontName] :: Theme -> String
-- | Maximum width of the decorations (if supported by the
-- DecorationStyle)
[decoWidth] :: Theme -> Dimension
-- | Height of the decorations
[decoHeight] :: Theme -> Dimension
-- | Extra text to appear in a window's title bar. Refer to for a use
-- XMonad.Layout.ImageButtonDecoration
[windowTitleAddons] :: Theme -> [(String, Align)]
-- | Extra icons to appear in a window's title bar. Inner [Bool]
-- is a row in a icon bitmap.
[windowTitleIcons] :: Theme -> [([[Bool]], Placement)]
-- | The default value for this type.
def :: Default a => a
-- | The default xmonad Theme.
-- | Deprecated: Use def (from Data.Default, and re-exported by
-- XMonad.Layout.Decoration) instead.
defaultTheme :: Theme
data TabbedDecoration a
Tabbed :: Direction2D -> TabbarShown -> TabbedDecoration a
shrinkText :: DefaultShrinker
data CustomShrink
CustomShrink :: CustomShrink
class (Read s, Show s) => Shrinker s
shrinkIt :: Shrinker s => s -> String -> [String]
data TabbarShown
-- | Two-dimensional directions:
data Direction2D
-- | Up
U :: Direction2D
-- | Down
D :: Direction2D
-- | Right
R :: Direction2D
-- | Left
L :: Direction2D
instance GHC.Show.Show (XMonad.Layout.Tabbed.TabbedDecoration a)
instance GHC.Read.Read (XMonad.Layout.Tabbed.TabbedDecoration a)
instance GHC.Classes.Eq XMonad.Layout.Tabbed.TabbarShown
instance GHC.Show.Show XMonad.Layout.Tabbed.TabbarShown
instance GHC.Read.Read XMonad.Layout.Tabbed.TabbarShown
instance GHC.Classes.Eq a => XMonad.Layout.Decoration.DecorationStyle XMonad.Layout.Tabbed.TabbedDecoration a
-- | WindowNavigation is an extension to allow easy navigation of a
-- workspace.
module XMonad.Layout.WindowNavigation
windowNavigation :: LayoutClass l a => l a -> ModifiedLayout WindowNavigation l a
configurableNavigation :: LayoutClass l a => WNConfig -> l a -> ModifiedLayout WindowNavigation l a
data Navigate
Go :: Direction2D -> Navigate
Swap :: Direction2D -> Navigate
Move :: Direction2D -> Navigate
-- | Apply action with destination window
Apply :: (Window -> X ()) -> Direction2D -> Navigate
-- | Two-dimensional directions:
data Direction2D
-- | Up
U :: Direction2D
-- | Down
D :: Direction2D
-- | Right
R :: Direction2D
-- | Left
L :: Direction2D
data MoveWindowToWindow a
MoveWindowToWindow :: a -> a -> MoveWindowToWindow a
navigateColor :: String -> WNConfig
navigateBrightness :: Double -> WNConfig
noNavigateBorders :: WNConfig
-- | Deprecated: Use def (from Data.Default, and re-exported by
-- XMonad.Layout.WindowNavigation) instead.
defaultWNConfig :: WNConfig
-- | The default value for this type.
def :: Default a => a
data WNConfig
data WindowNavigation a
instance GHC.Show.Show (XMonad.Layout.WindowNavigation.WindowNavigation a)
instance GHC.Read.Read (XMonad.Layout.WindowNavigation.WindowNavigation a)
instance GHC.Read.Read XMonad.Layout.WindowNavigation.WNConfig
instance GHC.Show.Show XMonad.Layout.WindowNavigation.WNConfig
instance GHC.Show.Show a => GHC.Show.Show (XMonad.Layout.WindowNavigation.MoveWindowToWindow a)
instance GHC.Read.Read a => GHC.Read.Read (XMonad.Layout.WindowNavigation.MoveWindowToWindow a)
instance Data.Typeable.Internal.Typeable a => XMonad.Core.Message (XMonad.Layout.WindowNavigation.MoveWindowToWindow a)
instance XMonad.Core.Message XMonad.Layout.WindowNavigation.Navigate
instance Data.Default.Class.Default XMonad.Layout.WindowNavigation.WNConfig
instance XMonad.Layout.LayoutModifier.LayoutModifier XMonad.Layout.WindowNavigation.WindowNavigation Graphics.X11.Types.Window
-- | A layout that combines multiple layouts.
module XMonad.Layout.Combo
combineTwo :: (Read a, Eq a, LayoutClass super (), LayoutClass l1 a, LayoutClass l2 a) => super () -> l1 a -> l2 a -> CombineTwo (super ()) l1 l2 a
data CombineTwo l l1 l2 a
instance (GHC.Show.Show l, GHC.Show.Show a, GHC.Show.Show (l1 a), GHC.Show.Show (l2 a)) => GHC.Show.Show (XMonad.Layout.Combo.CombineTwo l l1 l2 a)
instance (GHC.Read.Read l, GHC.Read.Read a, GHC.Read.Read (l1 a), GHC.Read.Read (l2 a)) => GHC.Read.Read (XMonad.Layout.Combo.CombineTwo l l1 l2 a)
instance (XMonad.Core.LayoutClass l (), XMonad.Core.LayoutClass l1 a, XMonad.Core.LayoutClass l2 a, GHC.Read.Read a, GHC.Show.Show a, GHC.Classes.Eq a, Data.Typeable.Internal.Typeable a) => XMonad.Core.LayoutClass (XMonad.Layout.Combo.CombineTwo (l ()) l1 l2) a
-- | A layout that combines multiple layouts and allows to specify where to
-- put new windows.
module XMonad.Layout.ComboP
combineTwoP :: (LayoutClass super (), LayoutClass l1 Window, LayoutClass l2 Window) => super () -> l1 Window -> l2 Window -> Property -> CombineTwoP (super ()) l1 l2 Window
data CombineTwoP l l1 l2 a
data SwapWindow
-- | Swap window between panes
SwapWindow :: SwapWindow
-- | Swap window between panes in the N-th nested ComboP. SwapWindowN
-- 0 equals to SwapWindow
SwapWindowN :: Int -> SwapWindow
-- | Most of the property constructors are quite self-explaining.
data Property
Title :: String -> Property
ClassName :: String -> Property
Resource :: String -> Property
-- | WM_WINDOW_ROLE property
Role :: String -> Property
-- | WM_CLIENT_MACHINE property
Machine :: String -> Property
And :: Property -> Property -> Property
Or :: Property -> Property -> Property
Not :: Property -> Property
Const :: Bool -> Property
instance (GHC.Show.Show l, GHC.Show.Show a, GHC.Show.Show (l1 a), GHC.Show.Show (l2 a)) => GHC.Show.Show (XMonad.Layout.ComboP.CombineTwoP l l1 l2 a)
instance (GHC.Read.Read l, GHC.Read.Read a, GHC.Read.Read (l1 a), GHC.Read.Read (l2 a)) => GHC.Read.Read (XMonad.Layout.ComboP.CombineTwoP l l1 l2 a)
instance GHC.Show.Show XMonad.Layout.ComboP.SwapWindow
instance GHC.Read.Read XMonad.Layout.ComboP.SwapWindow
instance XMonad.Core.Message XMonad.Layout.ComboP.SwapWindow
instance (XMonad.Core.LayoutClass l (), XMonad.Core.LayoutClass l1 Graphics.X11.Types.Window, XMonad.Core.LayoutClass l2 Graphics.X11.Types.Window) => XMonad.Core.LayoutClass (XMonad.Layout.ComboP.CombineTwoP (l ()) l1 l2) Graphics.X11.Types.Window
-- | Layout where new windows will split the focused window in half, based
-- off of BSPWM
module XMonad.Layout.BinarySpacePartition
-- | an empty BinarySpacePartition to use as a default for adding windows
-- to.
emptyBSP :: BinarySpacePartition a
-- | Message for rotating a split (horizontal/vertical) in the BSP
data Rotate
Rotate :: Rotate
-- | Message for swapping the left child of a split with the right child of
-- split
data Swap
Swap :: Swap
-- | Message for resizing one of the cells in the BSP
data ResizeDirectional
ExpandTowards :: Direction2D -> ResizeDirectional
ShrinkFrom :: Direction2D -> ResizeDirectional
MoveSplit :: Direction2D -> ResizeDirectional
-- | Message for rotating the binary tree around the parent node of the
-- window to the left or right
data TreeRotate
RotateL :: TreeRotate
RotateR :: TreeRotate
-- | Message to balance the tree in some way (Balance retiles the windows,
-- Equalize changes ratios)
data TreeBalance
Balance :: TreeBalance
Equalize :: TreeBalance
-- | Message to cyclically select the parent node instead of the leaf
data FocusParent
FocusParent :: FocusParent
-- | Message to move nodes inside the tree
data SelectMoveNode
SelectNode :: SelectMoveNode
MoveNode :: SelectMoveNode
-- | Two-dimensional directions:
data Direction2D
-- | Up
U :: Direction2D
-- | Down
D :: Direction2D
-- | Right
R :: Direction2D
-- | Left
L :: Direction2D
instance GHC.Classes.Eq (XMonad.Layout.BinarySpacePartition.BinarySpacePartition a)
instance GHC.Read.Read (XMonad.Layout.BinarySpacePartition.BinarySpacePartition a)
instance GHC.Show.Show (XMonad.Layout.BinarySpacePartition.BinarySpacePartition a)
instance GHC.Classes.Eq XMonad.Layout.BinarySpacePartition.NodeRef
instance GHC.Read.Read XMonad.Layout.BinarySpacePartition.NodeRef
instance GHC.Show.Show XMonad.Layout.BinarySpacePartition.NodeRef
instance GHC.Classes.Eq a => GHC.Classes.Eq (XMonad.Layout.BinarySpacePartition.Crumb a)
instance GHC.Read.Read a => GHC.Read.Read (XMonad.Layout.BinarySpacePartition.Crumb a)
instance GHC.Show.Show a => GHC.Show.Show (XMonad.Layout.BinarySpacePartition.Crumb a)
instance GHC.Classes.Eq a => GHC.Classes.Eq (XMonad.Layout.BinarySpacePartition.Tree a)
instance GHC.Read.Read a => GHC.Read.Read (XMonad.Layout.BinarySpacePartition.Tree a)
instance GHC.Show.Show a => GHC.Show.Show (XMonad.Layout.BinarySpacePartition.Tree a)
instance GHC.Classes.Eq XMonad.Layout.BinarySpacePartition.Split
instance GHC.Read.Read XMonad.Layout.BinarySpacePartition.Split
instance GHC.Show.Show XMonad.Layout.BinarySpacePartition.Split
instance GHC.Classes.Eq XMonad.Layout.BinarySpacePartition.Axis
instance GHC.Read.Read XMonad.Layout.BinarySpacePartition.Axis
instance GHC.Show.Show XMonad.Layout.BinarySpacePartition.Axis
instance XMonad.Core.Message XMonad.Layout.BinarySpacePartition.TreeRotate
instance XMonad.Core.Message XMonad.Layout.BinarySpacePartition.TreeBalance
instance XMonad.Core.Message XMonad.Layout.BinarySpacePartition.ResizeDirectional
instance XMonad.Core.Message XMonad.Layout.BinarySpacePartition.Rotate
instance XMonad.Core.Message XMonad.Layout.BinarySpacePartition.Swap
instance XMonad.Core.Message XMonad.Layout.BinarySpacePartition.FocusParent
instance XMonad.Core.Message XMonad.Layout.BinarySpacePartition.SelectMoveNode
instance XMonad.Core.LayoutClass XMonad.Layout.BinarySpacePartition.BinarySpacePartition Graphics.X11.Types.Window
-- | Three layouts: The first, Spiral, is a reimplementation of
-- spiral with, at least to me, more intuitive semantics. The
-- second, Dwindle, is inspired by a similar layout in awesome and
-- produces the same sequence of decreasing window sizes as Spiral but
-- pushes the smallest windows into a screen corner rather than the
-- centre. The third, Squeeze arranges all windows in one row or
-- in one column, with geometrically decreasing sizes.
module XMonad.Layout.Dwindle
-- | Layouts with geometrically decreasing window sizes. Spiral and
-- Dwindle split the screen into a rectangle for the first window
-- and a rectangle for the remaining windows, which is split recursively
-- to lay out these windows. Both layouts alternate between horizontal
-- and vertical splits.
--
-- In each recursive step, the split Direction2D determines the
-- placement of the remaining windows relative to the current window: to
-- the left, to the right, above or below. The split direction of the
-- first split is determined by the first layout parameter. The split
-- direction of the second step is rotated 90 degrees relative to the
-- first split direction according to the second layout parameter of type
-- Chirality. So, if the first split is R and the second
-- layout parameter is CW, then the second split is D.
--
-- For the Spiral layout, the same Chirality is used for
-- computing the split direction of each step from the split direction of
-- the previous step. For example, parameters R and CW
-- produces the direction sequence R, D, L,
-- U, R, D, L, U, ...
--
-- For the Dwindle layout, the Chirality alternates between
-- CW and CCW in each step. For example, parameters
-- U and CCW produce the direction sequence U,
-- L, U, L, ... because L is the CCW
-- rotation of U and U is the CW rotation of
-- L.
--
-- In each split, the current rectangle is split so that the ratio
-- between the size of the rectangle allocated to the current window and
-- the size of the rectangle allocated to the remaining windows is the
-- third layout parameter. This ratio can be altered using Expand
-- and Shrink messages. The former multiplies the ratio by the
-- fourth layout parameter. The latter divides the ratio by this
-- parameter.
--
-- Squeeze does not alternate between horizontal and vertical
-- splits and simply splits in the direction given as its first argument.
--
-- Parameters for both Dwindle and Spiral:
--
-- -- subLayout advanceInnerLayouts innerLayout outerLayout ---- --
-- myLayout = addTabs shrinkText def -- $ subLayout [0,1,2] (Simplest ||| Tall 1 0.2 0.5 ||| Circle) -- $ Tall 1 0.2 0.5 ||| Full --subLayout :: [Int] -> subl a -> l a -> ModifiedLayout (Sublayout subl) l a -- | subTabbed is a use of subLayout with addTabs to -- show decorations. subTabbed :: (Eq a, LayoutModifier (Sublayout Simplest) a, LayoutClass l a) => l a -> ModifiedLayout (Decoration TabbedDecoration DefaultShrinker) (ModifiedLayout (Sublayout Simplest) l) a -- | pullGroup, pushGroup allow you to merge windows or -- groups inheriting the position of the current window (pull) or the -- other window (push). -- -- pushWindow and pullWindow move individual windows -- between groups. They are less effective at preserving window -- positions. pushGroup :: Direction2D -> Navigate -- | pullGroup, pushGroup allow you to merge windows or -- groups inheriting the position of the current window (pull) or the -- other window (push). -- -- pushWindow and pullWindow move individual windows -- between groups. They are less effective at preserving window -- positions. pullGroup :: Direction2D -> Navigate -- | pullGroup, pushGroup allow you to merge windows or -- groups inheriting the position of the current window (pull) or the -- other window (push). -- -- pushWindow and pullWindow move individual windows -- between groups. They are less effective at preserving window -- positions. pushWindow :: Direction2D -> Navigate -- | pullGroup, pushGroup allow you to merge windows or -- groups inheriting the position of the current window (pull) or the -- other window (push). -- -- pushWindow and pullWindow move individual windows -- between groups. They are less effective at preserving window -- positions. pullWindow :: Direction2D -> Navigate -- | Apply a function on the stack belonging to the currently focused -- group. It works for rearranging windows and for changing focus. onGroup :: (Stack Window -> Stack Window) -> X () -- | Send a message to the currently focused sublayout. toSubl :: (Message a) => a -> X () -- | merge the window that would be focused by the function when applied to -- the W.Stack of all windows, with the current group removed. The given -- window should be focused by a sublayout. Example usage: -- withFocused (sendMessage . mergeDir W.focusDown') mergeDir :: (Stack Window -> Stack Window) -> Window -> GroupMsg Window -- | GroupMsg take window parameters to determine which group the action -- should be applied to data GroupMsg a -- | free the focused window from its tab stack UnMerge :: a -> GroupMsg a -- | separate the focused group into singleton groups UnMergeAll :: a -> GroupMsg a -- | merge the first group into the second group Merge :: a -> a -> GroupMsg a -- | make one large group, keeping the parameter focused MergeAll :: a -> GroupMsg a -- | used to the window named in the first argument to the second -- argument's group, this may be replaced by a combination of -- UnMerge and Merge Migrate :: a -> a -> GroupMsg a WithGroup :: (Stack a -> X (Stack a)) -> a -> GroupMsg a -- | the sublayout with the given window will get the message SubMessage :: SomeMessage -> a -> GroupMsg a data Broadcast -- | send a message to all sublayouts Broadcast :: SomeMessage -> Broadcast -- | defaultSublMap is an attempt to create a set of keybindings -- like the defaults ones but to be used as a submap for sending -- messages to the sublayout. defaultSublMap :: XConfig l -> Map (KeyMask, KeySym) (X ()) data Sublayout l a instance (GHC.Show.Show a, GHC.Show.Show (l a)) => GHC.Show.Show (XMonad.Layout.SubLayouts.Sublayout l a) instance (GHC.Read.Read a, GHC.Read.Read (l a)) => GHC.Read.Read (XMonad.Layout.SubLayouts.Sublayout l a) instance XMonad.Core.Message XMonad.Layout.SubLayouts.Broadcast instance Data.Typeable.Internal.Typeable a => XMonad.Core.Message (XMonad.Layout.SubLayouts.GroupMsg a) instance (GHC.Read.Read (l Graphics.X11.Types.Window), GHC.Show.Show (l Graphics.X11.Types.Window), XMonad.Core.LayoutClass l Graphics.X11.Types.Window) => XMonad.Layout.LayoutModifier.LayoutModifier (XMonad.Layout.SubLayouts.Sublayout l) Graphics.X11.Types.Window -- | Keeps track of workspace viewing order. module XMonad.Hooks.WorkspaceHistory -- | A logHook that keeps track of the order in which workspaces -- have been viewed. workspaceHistoryHook :: X () -- | A list of workspace tags in the order they have been viewed, with the -- most recent first. No duplicates are present, but not all workspaces -- are guaranteed to appear, and there may be workspaces that no longer -- exist. workspaceHistory :: X [WorkspaceId] instance GHC.Show.Show XMonad.Hooks.WorkspaceHistory.WorkspaceHistory instance GHC.Read.Read XMonad.Hooks.WorkspaceHistory.WorkspaceHistory instance XMonad.Core.ExtensionClass XMonad.Hooks.WorkspaceHistory.WorkspaceHistory -- | Provides bindings to cycle forward or backward through the list of -- workspaces, to move windows between workspaces, and to cycle between -- screens. More general combinators provide ways to cycle through -- workspaces in various orders, to only cycle through some subset of -- workspaces, and to cycle by more than one workspace at a time. -- -- Note that this module now subsumes the functionality of the former -- XMonad.Actions.RotView. Former users of rotView can -- simply replace rotView True with moveTo Next -- NonEmptyWS, and so on. -- -- If you want to exactly replicate the action of rotView -- (cycling through workspace in order lexicographically by tag, instead -- of in the order specified in the config), it can be implemented as: -- --
-- rotView b = do t <- findWorkspace getSortByTag (bToDir b) NonEmptyWS 1 -- windows . greedyView $ t -- where bToDir True = Next -- bToDir False = Prev --module XMonad.Actions.CycleWS -- | Switch to the next workspace. nextWS :: X () -- | Switch to the previous workspace. prevWS :: X () -- | Move the focused window to the next workspace. shiftToNext :: X () -- | Move the focused window to the previous workspace. shiftToPrev :: X () -- | Toggle to the workspace displayed previously. toggleWS :: X () -- | Toggle to the previous workspace while excluding some workspaces. -- --
-- -- Ignore the scratchpad workspace while toggling:
-- ("M-b", toggleWS' ["NSP"])
--
toggleWS' :: [WorkspaceId] -> X ()
-- | greedyView a workspace, or if already there, view the
-- previously displayed workspace ala weechat. Change greedyView
-- to toggleOrView in your workspace bindings as in the
-- view faq at
-- http://haskell.org/haskellwiki/Xmonad/Frequently_asked_questions.
-- For more flexibility see toggleOrDoSkip.
toggleOrView :: WorkspaceId -> X ()
-- | View next screen
nextScreen :: X ()
-- | View prev screen
prevScreen :: X ()
-- | Move focused window to workspace on next screen
shiftNextScreen :: X ()
-- | Move focused window to workspace on prev screen
shiftPrevScreen :: X ()
-- | Swap current screen with next screen
swapNextScreen :: X ()
-- | Swap current screen with previous screen
swapPrevScreen :: X ()
-- | One-dimensional directions:
data Direction1D
Next :: Direction1D
Prev :: Direction1D
-- | What type of workspaces should be included in the cycle?
data WSType
-- | cycle through empty workspaces
EmptyWS :: WSType
-- | cycle through non-empty workspaces
NonEmptyWS :: WSType
-- | cycle through non-visible workspaces
HiddenWS :: WSType
-- | cycle through non-empty non-visible workspaces
HiddenNonEmptyWS :: WSType
-- | cycle through all workspaces
AnyWS :: WSType
-- | cycle through workspaces in the same group, the group name is all
-- characters up to the first separator character or the end of the tag
WSTagGroup :: Char -> WSType
-- | cycle through workspaces satisfying an arbitrary predicate
WSIs :: (X (WindowSpace -> Bool)) -> WSType
-- | Move the currently focused window to the next workspace in the given
-- direction that satisfies the given condition.
shiftTo :: Direction1D -> WSType -> X ()
-- | View the next workspace in the given direction that satisfies the
-- given condition.
moveTo :: Direction1D -> WSType -> X ()
-- | Using the given sort, find the next workspace in the given direction
-- of the given type, and perform the given action on it.
doTo :: Direction1D -> WSType -> X WorkspaceSort -> (WorkspaceId -> X ()) -> X ()
-- | Given a function s to sort workspaces, a direction
-- dir, a predicate p on workspaces, and an integer
-- n, find the tag of the workspace which is n away
-- from the current workspace in direction dir (wrapping around
-- if necessary), among those workspaces, sorted by s, which
-- satisfy p.
--
-- For some useful workspace sorting functions, see
-- XMonad.Util.WorkspaceCompare.
--
-- For ideas of what to do with a workspace tag once obtained, note that
-- moveTo and shiftTo are implemented by applying
-- (>>= (windows . greedyView)) and (>>=
-- (windows . shift)), respectively, to the output of
-- findWorkspace.
findWorkspace :: X WorkspaceSort -> Direction1D -> WSType -> Int -> X WorkspaceId
-- | Allows ignoring listed workspace tags (such as scratchpad's "NSP"),
-- and running other actions such as view, shift, etc. For example:
--
-- -- import qualified XMonad.StackSet as W -- import XMonad.Actions.CycleWS -- -- -- toggleOrView for people who prefer view to greedyView -- toggleOrView' = toggleOrDoSkip [] W.view -- -- -- toggleOrView ignoring scratchpad and named scratchpad workspace -- toggleOrViewNoSP = toggleOrDoSkip ["NSP"] W.greedyView --toggleOrDoSkip :: [WorkspaceId] -> (WorkspaceId -> WindowSet -> WindowSet) -> WorkspaceId -> X () -- | List difference (\\) for workspaces and tags. Removes -- workspaces matching listed tags from the given workspace list. skipTags :: (Eq i) => [Workspace i l a] -> [i] -> [Workspace i l a] -- | Get the ScreenId d places over. Example usage is a -- variation of the the default screen keybindings: -- --
-- -- mod-{w,e}, Switch to previous/next Xinerama screen
-- -- mod-shift-{w,e}, Move client to previous/next Xinerama screen
-- --
-- [((m .|. modm, key), sc >>= screenWorkspace >>= flip whenJust (windows . f))
-- | (key, sc) <- zip [xK_w, xK_e] [(screenBy (-1)),(screenBy 1)]
-- , (f, m) <- [(W.view, 0), (W.shift, shiftMask)]]
--
screenBy :: Int -> X (ScreenId)
-- | Remember a dynamically updateable ordering on workspaces, together
-- with tools for using this ordering with XMonad.Actions.CycleWS
-- and XMonad.Hooks.DynamicLog.
module XMonad.Actions.DynamicWorkspaceOrder
-- | A comparison function which orders workspaces according to the stored
-- dynamic ordering.
getWsCompareByOrder :: X WorkspaceCompare
-- | Sort workspaces according to the stored dynamic ordering.
getSortByOrder :: X WorkspaceSort
-- | Swap the current workspace with another workspace in the stored
-- dynamic order.
swapWith :: Direction1D -> WSType -> X ()
-- | View the next workspace of the given type in the given direction,
-- where "next" is determined using the dynamic workspace order.
moveTo :: Direction1D -> WSType -> X ()
-- | Same as moveTo, but using greedyView instead of
-- view.
moveToGreedy :: Direction1D -> WSType -> X ()
-- | Shift the currently focused window to the next workspace of the given
-- type in the given direction, using the dynamic workspace order.
shiftTo :: Direction1D -> WSType -> X ()
-- | Do something with the nth workspace in the dynamic order. The callback
-- is given the workspace's tag as well as the WindowSet of the
-- workspace itself.
withNthWorkspace :: (String -> WindowSet -> WindowSet) -> Int -> X ()
instance GHC.Show.Show XMonad.Actions.DynamicWorkspaceOrder.WSOrderStorage
instance GHC.Read.Read XMonad.Actions.DynamicWorkspaceOrder.WSOrderStorage
instance XMonad.Core.ExtensionClass XMonad.Actions.DynamicWorkspaceOrder.WSOrderStorage
-- | Lets you swap workspace tags, so you can keep related ones next to
-- each other, without having to move individual windows.
module XMonad.Actions.SwapWorkspaces
-- | Swaps the currently focused workspace with the given workspace tag,
-- via swapWorkspaces.
swapWithCurrent :: Eq i => i -> StackSet i l a s sd -> StackSet i l a s sd
-- | Say swapTo Next or swapTo Prev to move your current
-- workspace. This is an X () so can be hooked up to your
-- keybindings directly.
swapTo :: Direction1D -> X ()
-- | Takes two workspace tags and an existing XMonad.StackSet and returns a
-- new one with the two corresponding workspaces' tags swapped.
swapWorkspaces :: Eq i => i -> i -> StackSet i l a s sd -> StackSet i l a s sd
-- | One-dimensional directions:
data Direction1D
Next :: Direction1D
Prev :: Direction1D
-- | Provides bindings to rename workspaces, show these names in DynamicLog
-- and swap workspaces along with their names. These names survive
-- restart. Together with XMonad.Layout.WorkspaceDir this provides
-- for a fully dynamic topic space workflow.
module XMonad.Actions.WorkspaceNames
-- | Prompt for a new name for the current workspace and set it.
renameWorkspace :: XPConfig -> X ()
-- | Modify XMonad.Hooks.DynamicLog's pretty-printing format to show
-- workspace names as well.
workspaceNamesPP :: PP -> X PP
-- | Returns a function that maps workspace tag "t" to
-- "t:name" for workspaces with a name, and to "t"
-- otherwise.
getWorkspaceNames :: X (WorkspaceId -> String)
-- | Sets the name of a workspace. Empty string makes the workspace unnamed
-- again.
setWorkspaceName :: WorkspaceId -> String -> X ()
-- | Sets the name of the current workspace. See setWorkspaceName.
setCurrentWorkspaceName :: String -> X ()
-- | See swapTo. This is the same with names.
swapTo :: Direction1D -> X ()
-- | Swap with the previous or next workspace of the given type.
swapTo' :: Direction1D -> WSType -> X ()
-- | See swapWithCurrent. This is almost the same with names.
swapWithCurrent :: WorkspaceId -> X ()
-- | Same behavior than workspacePrompt excepted it acts on the
-- workspace name provided by this module.
workspaceNamePrompt :: XPConfig -> (String -> X ()) -> X ()
instance GHC.Show.Show XMonad.Actions.WorkspaceNames.WorkspaceNames
instance GHC.Read.Read XMonad.Actions.WorkspaceNames.WorkspaceNames
instance XMonad.Core.ExtensionClass XMonad.Actions.WorkspaceNames.WorkspaceNames
-- | Rotate all windows except the master window and keep the focus in
-- place.
module XMonad.Actions.RotSlaves
-- | The actual rotation, as a pure function on the window stack.
rotSlaves' :: ([a] -> [a]) -> Stack a -> Stack a
-- | Rotate the windows in the current stack, excluding the first one
-- (master).
rotSlavesUp :: X ()
-- | Rotate the windows in the current stack, excluding the first one
-- (master).
rotSlavesDown :: X ()
-- | The actual rotation, as a pure function on the window stack.
rotAll' :: ([a] -> [a]) -> Stack a -> Stack a
-- | Rotate all the windows in the current stack.
rotAllUp :: X ()
-- | Rotate all the windows in the current stack.
rotAllDown :: X ()
-- | Provides bindings to cycle windows up or down on the current workspace
-- stack while maintaining focus in place.
--
-- Bindings are available to:
--
-- -- , ((modm, xK_m), raiseMaybe (runInTerm "-title mutt" "mutt") (title =? "mutt")) --raiseMaybe :: X () -> Query Bool -> X () -- | See raiseMaybe. raiseNextMaybe is an alternative version -- that allows cycling through the matching windows. If the focused -- window matches the query the next matching window is raised. If no -- matches are found the function f is executed. raiseNextMaybe :: X () -> Query Bool -> X () -- | raiseBrowser and raiseEditor grab $BROWSER and $EDITOR -- respectively and they either take you to the specified program's -- window, or they try to run it. This is most useful if your variables -- are simple and look like "firefox" or "emacs". raiseBrowser :: X () -- | raiseBrowser and raiseEditor grab $BROWSER and $EDITOR -- respectively and they either take you to the specified program's -- window, or they try to run it. This is most useful if your variables -- are simple and look like "firefox" or "emacs". raiseEditor :: X () -- | If a window matching the second argument is found, the window is -- focused and the third argument is called; otherwise, the first -- argument is called. runOrRaiseAndDo :: String -> Query Bool -> (Window -> X ()) -> X () -- | If the window is found the window is focused and set to master -- otherwise, action is run. -- --
-- runOrRaiseMaster "firefox" (className =? "Firefox")) --runOrRaiseMaster :: String -> Query Bool -> X () -- | If the window is found the window is focused and the third argument is -- called otherwise, the first argument is called See raiseMaster -- for an example. raiseAndDo :: X () -> Query Bool -> (Window -> X ()) -> X () -- | if the window is found the window is focused and set to master -- otherwise, the first argument is called. -- --
-- raiseMaster (runInTerm "-title ghci" "zsh -c 'ghci'") (title =? "ghci") --raiseMaster :: X () -> Query Bool -> X () -- | If windows that satisfy the query exist, apply the supplied function -- to them, otherwise run the action given as second parameter. ifWindows :: Query Bool -> ([Window] -> X ()) -> X () -> X () -- | The same as ifWindows, but applies a ManageHook to the first match -- instead and discards the other matches ifWindow :: Query Bool -> ManageHook -> X () -> X () -- | A manage hook that raises the window. raiseHook :: ManageHook -- | A prompt for XMonad which will run a program, open a file, or raise an -- already running program, depending on context. module XMonad.Prompt.RunOrRaise runOrRaisePrompt :: XPConfig -> X () data RunOrRaisePrompt instance XMonad.Prompt.XPrompt XMonad.Prompt.RunOrRaise.RunOrRaisePrompt -- | Provides bindings to duplicate a window on multiple workspaces, -- providing dwm-like tagging functionality. module XMonad.Actions.CopyWindow -- | Copy the focused window to a workspace. copy :: (Eq s, Eq i, Eq a) => i -> StackSet i l a s sd -> StackSet i l a s sd -- | Copy the focused window to all workspaces. copyToAll :: (Eq s, Eq i, Eq a) => StackSet i l a s sd -> StackSet i l a s sd -- | Copy an arbitrary window to a workspace. copyWindow :: (Eq a, Eq i, Eq s) => a -> i -> StackSet i l a s sd -> StackSet i l a s sd -- | runOrCopy will run the provided shell command unless it can find a -- specified window in which case it will copy the window to the current -- workspace. Similar to (i.e., stolen from) -- XMonad.Actions.WindowGo. runOrCopy :: String -> Query Bool -> X () -- | Kill all other copies of focused window (if they're present). 'All -- other' means here 'copies which are not on the current workspace'. killAllOtherCopies :: X () -- | Remove the focused window from this workspace. If it's present in no -- other workspace, then kill it instead. If we do kill it, we'll get a -- delete notify back from X. -- -- There are two ways to delete a window. Either just kill it, or if it -- supports the delete protocol, send a delete event (e.g. firefox). kill1 :: X () -- | A list of hidden workspaces containing a copy of the focused window. wsContainingCopies :: X [WorkspaceId] module XMonad.Config.Sjanssen sjanssenConfig :: XConfig (ModifiedLayout AvoidStruts (ModifiedLayout SmartBorder (Choose (Choose HintedTile (Choose HintedTile Full)) (ModifiedLayout (Decoration TabbedDecoration DefaultShrinker) Simplest)))) -- | Lets you constrain the aspect ratio of a floating window (by, say, -- holding shift while you resize). -- -- Useful for making a nice circular XClock window. module XMonad.Actions.ConstrainedResize -- | Resize (floating) window with optional aspect ratio constraints. mouseResizeWindow :: Window -> Bool -> X () -- | A convenient binding to dmenu. -- -- Requires the process-1.0 package module XMonad.Util.Dmenu -- | Run dmenu to select an option from a list. dmenu :: [String] -> X String -- | Starts dmenu on the current screen. Requires this patch to dmenu: -- http://www.jcreigh.com/dmenu/dmenu-3.2-xinerama.patch dmenuXinerama :: [String] -> X String -- | Run dmenu to select an entry from a map based on the key. dmenuMap :: Map String a -> X (Maybe a) -- | like dmenu but also takes the command to run. menu :: String -> [String] -> X String -- | Like menu but also takes a list of command line arguments. menuArgs :: String -> [String] -> [String] -> X String -- | Like dmenuMap but also takes the command to run. menuMap :: String -> Map String a -> X (Maybe a) -- | Like menuMap but also takes a list of command line arguments. menuMapArgs :: String -> [String] -> Map String a -> X (Maybe a) -- | dmenu operations to bring windows to you, and bring you to windows. -- That is to say, it pops up a dmenu with window names, in case you -- forgot where you left your XChat. module XMonad.Actions.WindowBringer -- | Pops open a dmenu with window titles. Choose one, and you will be -- taken to the corresponding workspace. gotoMenu :: X () -- | Pops open an application with window titles given over stdin. Choose -- one, and you will be taken to the corresponding workspace. gotoMenu' :: String -> X () -- | Pops open a dmenu with window titles. Choose one, and you will be -- taken to the corresponding workspace. This version takes a list of -- arguments to pass to dmenu. gotoMenuArgs :: [String] -> X () -- | Pops open an application with window titles given over stdin. Choose -- one, and you will be taken to the corresponding workspace. This -- version takes a list of arguments to pass to dmenu. gotoMenuArgs' :: String -> [String] -> X () -- | Pops open a dmenu with window titles. Choose one, and it will be -- dragged, kicking and screaming, into your current workspace. bringMenu :: X () -- | Pops open an application with window titles given over stdin. Choose -- one, and it will be dragged, kicking and screaming, into your current -- workspace. bringMenu' :: String -> X () -- | Pops open a dmenu with window titles. Choose one, and it will be -- dragged, kicking and screaming, into your current workspace. This -- version takes a list of arguments to pass to dmenu. bringMenuArgs :: [String] -> X () -- | Pops open an application with window titles given over stdin. Choose -- one, and it will be dragged, kicking and screaming, into your current -- workspace. This version allows arguments to the chooser to be -- specified. bringMenuArgs' :: String -> [String] -> X () -- | A map from window names to Windows. windowMap :: X (Map String Window) -- | Brings the specified window into the current workspace. bringWindow :: Window -> WindowSet -> WindowSet -- | GridSelect displays items(e.g. the opened windows) in a 2D grid and -- lets the user select from it with the cursor/hjkl keys or the mouse. module XMonad.Actions.GridSelect -- | The Default instance gives a basic configuration for -- gridselect, with the colorizer chosen based on the type. -- -- If you want to replace the gs_colorizer field, use -- buildDefaultGSConfig instead of def to avoid ambiguous -- type variables. data GSConfig a GSConfig :: Integer -> Integer -> Integer -> (a -> Bool -> X (String, String)) -> String -> TwoD a (Maybe a) -> Rearranger a -> Double -> Double -> GSConfig a [gs_cellheight] :: GSConfig a -> Integer [gs_cellwidth] :: GSConfig a -> Integer [gs_cellpadding] :: GSConfig a -> Integer [gs_colorizer] :: GSConfig a -> a -> Bool -> X (String, String) [gs_font] :: GSConfig a -> String [gs_navigate] :: GSConfig a -> TwoD a (Maybe a) [gs_rearranger] :: GSConfig a -> Rearranger a [gs_originFractX] :: GSConfig a -> Double [gs_originFractY] :: GSConfig a -> Double -- | The default value for this type. def :: Default a => a -- | Deprecated: Use def (from Data.Default, and re-exported from -- XMonad.Actions.GridSelect) instead. defaultGSConfig :: HasColorizer a => GSConfig a type TwoDPosition = (Integer, Integer) -- | Builds a default gs config from a colorizer function. buildDefaultGSConfig :: (a -> Bool -> X (String, String)) -> GSConfig a -- | Brings up a 2D grid of elements in the center of the screen, and one -- can select an element with cursors keys. The selected element is -- returned. gridselect :: GSConfig a -> [(String, a)] -> X (Maybe a) -- | Like gridSelect but with the current windows and their titles -- as elements gridselectWindow :: GSConfig Window -> X (Maybe Window) -- | Brings up a 2D grid of windows in the center of the screen, and one -- can select a window with cursors keys. The selected window is then -- passed to a callback function. withSelectedWindow :: (Window -> X ()) -> GSConfig Window -> X () -- | Brings selected window to the current workspace. bringSelected :: GSConfig Window -> X () -- | Switches to selected window's workspace and focuses that window. goToSelected :: GSConfig Window -> X () -- | Select a workspace and view it using the given function (normally -- view or greedyView) -- -- Another option is to shift the current window to the selected -- workspace: -- --
-- gridselectWorkspace (\ws -> W.greedyView ws . W.shift ws) --gridselectWorkspace :: GSConfig WorkspaceId -> (WorkspaceId -> WindowSet -> WindowSet) -> X () -- | Select a workspace and run an arbitrary action on it. gridselectWorkspace' :: GSConfig WorkspaceId -> (WorkspaceId -> X ()) -> X () -- | Select an application to spawn from a given list spawnSelected :: GSConfig String -> [String] -> X () -- | Select an action and run it in the X monad runSelectedAction :: GSConfig (X ()) -> [(String, X ())] -> X () -- | That is fromClassName if you are selecting a Window, or -- defaultColorizer if you are selecting a String. The -- catch-all instance HasColorizer a uses the -- focusedBorderColor and normalBorderColor colors. class HasColorizer a defaultColorizer :: HasColorizer a => a -> Bool -> X (String, String) -- | Colorize a window depending on it's className. fromClassName :: Window -> Bool -> X (String, String) -- | Default colorizer for Strings stringColorizer :: String -> Bool -> X (String, String) -- | A colorizer that picks a color inside a range, and depending on the -- window's class. colorRangeFromClassName :: (Word8, Word8, Word8) -> (Word8, Word8, Word8) -> (Word8, Word8, Word8) -> (Word8, Word8, Word8) -> (Word8, Word8, Word8) -> Window -> Bool -> X (String, String) data TwoD a b -- | Embeds a key handler into the X event handler that dispatches key -- events to the key handler, while non-key event go to the standard -- handler. makeXEventhandler :: ((KeySym, String, KeyMask) -> TwoD a (Maybe a)) -> TwoD a (Maybe a) -- | When the map contains (KeySym,KeyMask) tuple for the given event, the -- associated action in the map associated shadows the default key -- handler shadowWithKeymap :: Map (KeyMask, KeySym) a -> ((KeySym, String, KeyMask) -> a) -> (KeySym, String, KeyMask) -> a -- | By default gridselect used the defaultNavigation action, which binds -- left,right,up,down and vi-style h,l,j,k navigation. Return quits -- gridselect, returning the selected element, while Escape cancels the -- selection. Slash enters the substring search mode. In substring search -- mode, every string-associated keystroke is added to a search string, -- which narrows down the object selection. Substring search mode comes -- back to regular navigation via Return, while Escape cancels the -- search. If you want that navigation style, add -- defaultNavigation as gs_navigate to your GSConfig -- object. This is done by buildDefaultGSConfig automatically. defaultNavigation :: TwoD a (Maybe a) -- | Navigation submode used for substring search. It returns to the first -- argument navigation style when the user hits Return. substringSearch :: TwoD a (Maybe a) -> TwoD a (Maybe a) -- | This navigation style combines navigation and search into one mode at -- the cost of losing vi style navigation. With this style, there is no -- substring search submode, but every typed character is added to the -- substring search. navNSearch :: TwoD a (Maybe a) -- | Sets the absolute position of the cursor. setPos :: (Integer, Integer) -> TwoD a () -- | Moves the cursor by the offsets specified move :: (Integer, Integer) -> TwoD a () moveNext :: TwoD a () movePrev :: TwoD a () -- | Closes gridselect returning the element under the cursor select :: TwoD a (Maybe a) -- | Closes gridselect returning no element. cancel :: TwoD a (Maybe a) -- | Apply a transformation function the current search string transformSearchString :: (String -> String) -> TwoD a () -- | A function taking the search string and a list of elements, and -- returning a potentially rearranged list of elements. type Rearranger a = String -> [(String, a)] -> X [(String, a)] -- | A rearranger that leaves the elements unmodified. noRearranger :: Rearranger a -- | A generator for rearrangers that append a single element based on the -- search string, if doing so would not be redundant (empty string or -- value already present). searchStringRearrangerGenerator :: (String -> a) -> Rearranger a data TwoDState a instance Control.Monad.State.Class.MonadState (XMonad.Actions.GridSelect.TwoDState a) (XMonad.Actions.GridSelect.TwoD a) instance GHC.Base.Functor (XMonad.Actions.GridSelect.TwoD a) instance GHC.Base.Monad (XMonad.Actions.GridSelect.TwoD a) instance XMonad.Actions.GridSelect.HasColorizer Graphics.X11.Types.Window instance XMonad.Actions.GridSelect.HasColorizer GHC.Base.String instance XMonad.Actions.GridSelect.HasColorizer a instance XMonad.Actions.GridSelect.HasColorizer a => Data.Default.Class.Default (XMonad.Actions.GridSelect.GSConfig a) instance GHC.Base.Applicative (XMonad.Actions.GridSelect.TwoD a) -- | Uses XMonad.Actions.GridSelect to display a number of actions -- related to window management in the center of the focused window. -- Actions include: Closing, maximizing, minimizing and shifting the -- window to another workspace. -- -- Note: For maximizing and minimizing to actually work, you will need to -- integrate XMonad.Layout.Maximize and -- XMonad.Layout.Minimize into your setup. See the documentation -- of those modules for more information. module XMonad.Actions.WindowMenu windowMenu :: X () -- | Various stuff that can be added to the decoration. Most of it is -- intended to be used by other modules. See -- XMonad.Layout.ButtonDecoration for a module that makes use of -- this. module XMonad.Layout.DecorationAddons -- | A function intended to be plugged into the -- decorationCatchClicksHook of a decoration. It will intercept -- clicks on the buttons of the decoration and invoke the associated -- action. To actually see the buttons, you will need to use a theme that -- includes them. See defaultThemeWithButtons below. titleBarButtonHandler :: Window -> Int -> Int -> X Bool -- | Intended to be used together with titleBarButtonHandler. See -- above. defaultThemeWithButtons :: Theme -- | A function intended to be plugged into the -- decorationAfterDraggingHook of a decoration. It will check if -- the window has been dragged onto another screen and shift it there. -- The PositionStore is also updated accordingly, as this is designed to -- be used together with XMonad.Layout.PositionStoreFloat. handleScreenCrossing :: Window -> Window -> X Bool -- | A decoration that includes small buttons on both ends which invoke -- various actions when clicked on: Show a window menu (see -- XMonad.Actions.WindowMenu), minimize, maximize or close the -- window. -- -- Note: For maximizing and minimizing to actually work, you will need to -- integrate XMonad.Layout.Maximize and -- XMonad.Layout.Minimize into your setup. See the documentation -- of those modules for more information. module XMonad.Layout.ButtonDecoration buttonDeco :: (Eq a, Shrinker s) => s -> Theme -> l a -> ModifiedLayout (Decoration ButtonDecoration s) l a data ButtonDecoration a instance GHC.Read.Read (XMonad.Layout.ButtonDecoration.ButtonDecoration a) instance GHC.Show.Show (XMonad.Layout.ButtonDecoration.ButtonDecoration a) instance GHC.Classes.Eq a => XMonad.Layout.Decoration.DecorationStyle XMonad.Layout.ButtonDecoration.ButtonDecoration a -- | A decoration that includes small image buttons on both ends which -- invoke various actions when clicked on: Show a window menu (see -- XMonad.Actions.WindowMenu), minimize, maximize or close the -- window. -- -- Note: For maximizing and minimizing to actually work, you will need to -- integrate XMonad.Layout.Maximize and -- XMonad.Layout.Minimize into your setup. See the documentation -- of those modules for more information. module XMonad.Layout.ImageButtonDecoration imageButtonDeco :: (Eq a, Shrinker s) => s -> Theme -> l a -> ModifiedLayout (Decoration ImageButtonDecoration s) l a defaultThemeWithImageButtons :: Theme -- | A function intended to be plugged into the -- decorationCatchClicksHook of a decoration. It will intercept -- clicks on the buttons of the decoration and invoke the associated -- action. To actually see the buttons, you will need to use a theme that -- includes them. See defaultThemeWithImageButtons below. imageTitleBarButtonHandler :: Window -> Int -> Int -> X Bool data ImageButtonDecoration a instance GHC.Read.Read (XMonad.Layout.ImageButtonDecoration.ImageButtonDecoration a) instance GHC.Show.Show (XMonad.Layout.ImageButtonDecoration.ImageButtonDecoration a) instance GHC.Classes.Eq a => XMonad.Layout.Decoration.DecorationStyle XMonad.Layout.ImageButtonDecoration.ImageButtonDecoration a -- | A decoration that allows to switch the position of windows by dragging -- them onto each other. module XMonad.Layout.WindowSwitcherDecoration windowSwitcherDecoration :: (Eq a, Shrinker s) => s -> Theme -> l a -> ModifiedLayout (Decoration WindowSwitcherDecoration s) l a windowSwitcherDecorationWithButtons :: (Eq a, Shrinker s) => s -> Theme -> l a -> ModifiedLayout (Decoration WindowSwitcherDecoration s) l a windowSwitcherDecorationWithImageButtons :: (Eq a, Shrinker s) => s -> Theme -> l a -> ModifiedLayout (Decoration ImageWindowSwitcherDecoration s) l a data WindowSwitcherDecoration a data ImageWindowSwitcherDecoration a instance GHC.Read.Read (XMonad.Layout.WindowSwitcherDecoration.ImageWindowSwitcherDecoration a) instance GHC.Show.Show (XMonad.Layout.WindowSwitcherDecoration.ImageWindowSwitcherDecoration a) instance GHC.Read.Read (XMonad.Layout.WindowSwitcherDecoration.WindowSwitcherDecoration a) instance GHC.Show.Show (XMonad.Layout.WindowSwitcherDecoration.WindowSwitcherDecoration a) instance GHC.Classes.Eq a => XMonad.Layout.Decoration.DecorationStyle XMonad.Layout.WindowSwitcherDecoration.WindowSwitcherDecoration a instance GHC.Classes.Eq a => XMonad.Layout.Decoration.DecorationStyle XMonad.Layout.WindowSwitcherDecoration.ImageWindowSwitcherDecoration a -- | xprompt operations to bring windows to you, and bring you to windows. module XMonad.Prompt.Window windowPromptGoto :: XPConfig -> X () windowPromptBring :: XPConfig -> X () windowPromptBringCopy :: XPConfig -> X () data WindowPrompt instance XMonad.Prompt.XPrompt XMonad.Prompt.Window.WindowPrompt -- | Allows you to run internal xmonad commands (X () actions) using a -- dmenu menu in addition to key bindings. Requires dmenu and the Dmenu -- XMonad.Actions module. module XMonad.Actions.Commands -- | Create a Map from Strings to xmonad actions from a -- list of pairs. commandMap :: [(String, X ())] -> Map String (X ()) -- | Given a list of command/action pairs, prompt the user to choose a -- command and return the corresponding action. runCommand :: [(String, X ())] -> X () -- | Given the name of a command from defaultCommands, return the -- corresponding action (or the null action if the command is not found). runCommand' :: String -> X () -- | Generate a list of commands to switch to/send windows to workspaces. workspaceCommands :: X [(String, X ())] -- | Generate a list of commands dealing with multiple screens. screenCommands :: [(String, X ())] -- | A nice pre-defined list of commands. defaultCommands :: X [(String, X ())] -- | This is an EventHook that will receive commands from an -- external client. Also consider XMonad.Hooks.EwmhDesktops -- together with wmctrl. -- -- This is the example of a client: -- --
-- import Graphics.X11.Xlib
-- import Graphics.X11.Xlib.Extras
-- import System.Environment
-- import System.IO
-- import Data.Char
--
-- main :: IO ()
-- main = parse True "XMONAD_COMMAND" =<< getArgs
--
-- parse :: Bool -> String -> [String] -> IO ()
-- parse input addr args = case args of
-- ["--"] | input -> repl addr
-- | otherwise -> return ()
-- ("--":xs) -> sendAll addr xs
-- ("-a":a:xs) -> parse input a xs
-- ("-h":_) -> showHelp
-- ("--help":_) -> showHelp
-- ("-?":_) -> showHelp
-- (a@('-':_):_) -> hPutStrLn stderr ("Unknown option " ++ a)
--
-- (x:xs) -> sendCommand addr x >> parse False addr xs
-- [] | input -> repl addr
-- | otherwise -> return ()
--
--
-- repl :: String -> IO ()
-- repl addr = do e <- isEOF
-- case e of
-- True -> return ()
-- False -> do l <- getLine
-- sendCommand addr l
-- repl addr
--
-- sendAll :: String -> [String] -> IO ()
-- sendAll addr ss = foldr (\a b -> sendCommand addr a >> b) (return ()) ss
--
-- sendCommand :: String -> String -> IO ()
-- sendCommand addr s = do
-- d <- openDisplay ""
-- rw <- rootWindow d $ defaultScreen d
-- a <- internAtom d addr False
-- m <- internAtom d s False
-- allocaXEvent $ \e -> do
-- setEventType e clientMessage
-- setClientMessageEvent e rw a 32 m currentTime
-- sendEvent d rw False structureNotifyMask e
-- sync d False
--
-- showHelp :: IO ()
-- showHelp = do pn <- getProgName
-- putStrLn ("Send commands to a running instance of xmonad. xmonad.hs must be configured with XMonad.Hooks.ServerMode to work.\n-a atomname can be used at any point in the command line arguments to change which atom it is sending on.\nIf sent with no arguments or only -a atom arguments, it will read commands from stdin.\nEx:\n" ++ pn ++ " cmd1 cmd2\n" ++ pn ++ " -a XMONAD_COMMAND cmd1 cmd2 cmd3 -a XMONAD_PRINT hello world\n" ++ pn ++ " -a XMONAD_PRINT # will read data from stdin.\nThe atom defaults to XMONAD_COMMAND.")
--
--
-- compile with: ghc --make xmonadctl.hs
--
-- run with
--
-- -- xmonadctl command ---- -- or with -- --
-- $ xmonadctl -- command1 -- command2 -- . -- . -- . -- ^D ---- -- Usage will change depending on which event hook(s) you use. More -- examples are shown below. module XMonad.Hooks.ServerMode -- | Executes a command of the list when receiving its index via a special -- ClientMessageEvent (indexing starts at 1). Sending index 0 will ask -- xmonad to print the list of command numbers in stderr (so that you can -- read it in ~/.xsession-errors). Uses -- XMonad.Actions.Commands#defaultCommands as the default. -- --
-- main = xmonad def { handleEventHook = serverModeEventHook }
--
--
-- -- xmonadctl 0 # tells xmonad to output command list -- xmonadctl 1 # tells xmonad to switch to workspace 1 --serverModeEventHook :: Event -> X All -- | serverModeEventHook' additionally takes an action to generate the list -- of commands. serverModeEventHook' :: X [(String, X ())] -> Event -> X All -- | Executes a command of the list when receiving its name via a special -- ClientMessageEvent. Uses -- XMonad.Actions.Commands#defaultCommands as the default. -- --
-- main = xmonad def { handleEventHook = serverModeEventHookCmd }
--
--
-- -- xmonadctl run # Tells xmonad to generate a run prompt --serverModeEventHookCmd :: Event -> X All -- | Additionally takes an action to generate the list of commands serverModeEventHookCmd' :: X [(String, X ())] -> Event -> X All -- | Listens for an atom, then executes a callback function whenever it -- hears it. A trivial example that prints everything supplied to it on -- xmonad's standard out: -- --
-- main = xmonad def { handleEventHook = serverModeEventHookF "XMONAD_PRINT" (io . putStrLn) }
--
--
-- -- xmonadctl -a XMONAD_PRINT "hello world" --serverModeEventHookF :: String -> (String -> X ()) -> Event -> X All -- | A prompt for running XMonad commands module XMonad.Prompt.XMonad xmonadPrompt :: XPConfig -> X () -- | An xmonad prompt with a custom command list xmonadPromptC :: [(String, X ())] -> XPConfig -> X () data XMonad instance XMonad.Prompt.XPrompt XMonad.Prompt.XMonad.XMonad -- | The XMonad.Layout.LayoutCombinators module provides combinators -- for easily combining multiple layouts into one composite layout, as -- well as a way to jump directly to any particular layout (say, with a -- keybinding) without having to cycle through other layouts to get to -- it. module XMonad.Layout.LayoutCombinators (*||*) :: (Read a, Eq a, LayoutClass l1 a, LayoutClass l2 a) => l1 a -> l2 a -> CombineTwo (DragPane ()) l1 l2 a (**||*) :: (Read a, Eq a, LayoutClass l1 a, LayoutClass l2 a) => l1 a -> l2 a -> CombineTwo (DragPane ()) l1 l2 a (***||*) :: (Read a, Eq a, LayoutClass l1 a, LayoutClass l2 a) => l1 a -> l2 a -> CombineTwo (DragPane ()) l1 l2 a (****||*) :: (Read a, Eq a, LayoutClass l1 a, LayoutClass l2 a) => l1 a -> l2 a -> CombineTwo (DragPane ()) l1 l2 a (***||**) :: (Read a, Eq a, LayoutClass l1 a, LayoutClass l2 a) => l1 a -> l2 a -> CombineTwo (DragPane ()) l1 l2 a (****||***) :: (Read a, Eq a, LayoutClass l1 a, LayoutClass l2 a) => l1 a -> l2 a -> CombineTwo (DragPane ()) l1 l2 a (***||****) :: (Read a, Eq a, LayoutClass l1 a, LayoutClass l2 a) => l1 a -> l2 a -> CombineTwo (DragPane ()) l1 l2 a (*||****) :: (Read a, Eq a, LayoutClass l1 a, LayoutClass l2 a) => l1 a -> l2 a -> CombineTwo (DragPane ()) l1 l2 a (**||***) :: (Read a, Eq a, LayoutClass l1 a, LayoutClass l2 a) => l1 a -> l2 a -> CombineTwo (DragPane ()) l1 l2 a (*||***) :: (Read a, Eq a, LayoutClass l1 a, LayoutClass l2 a) => l1 a -> l2 a -> CombineTwo (DragPane ()) l1 l2 a (*||**) :: (Read a, Eq a, LayoutClass l1 a, LayoutClass l2 a) => l1 a -> l2 a -> CombineTwo (DragPane ()) l1 l2 a (*//*) :: (Read a, Eq a, LayoutClass l1 a, LayoutClass l2 a) => l1 a -> l2 a -> CombineTwo (DragPane ()) l1 l2 a (**//*) :: (Read a, Eq a, LayoutClass l1 a, LayoutClass l2 a) => l1 a -> l2 a -> CombineTwo (DragPane ()) l1 l2 a (***//*) :: (Read a, Eq a, LayoutClass l1 a, LayoutClass l2 a) => l1 a -> l2 a -> CombineTwo (DragPane ()) l1 l2 a (****//*) :: (Read a, Eq a, LayoutClass l1 a, LayoutClass l2 a) => l1 a -> l2 a -> CombineTwo (DragPane ()) l1 l2 a (***//**) :: (Read a, Eq a, LayoutClass l1 a, LayoutClass l2 a) => l1 a -> l2 a -> CombineTwo (DragPane ()) l1 l2 a (****//***) :: (Read a, Eq a, LayoutClass l1 a, LayoutClass l2 a) => l1 a -> l2 a -> CombineTwo (DragPane ()) l1 l2 a (***//****) :: (Read a, Eq a, LayoutClass l1 a, LayoutClass l2 a) => l1 a -> l2 a -> CombineTwo (DragPane ()) l1 l2 a (*//****) :: (Read a, Eq a, LayoutClass l1 a, LayoutClass l2 a) => l1 a -> l2 a -> CombineTwo (DragPane ()) l1 l2 a (**//***) :: (Read a, Eq a, LayoutClass l1 a, LayoutClass l2 a) => l1 a -> l2 a -> CombineTwo (DragPane ()) l1 l2 a (*//***) :: (Read a, Eq a, LayoutClass l1 a, LayoutClass l2 a) => l1 a -> l2 a -> CombineTwo (DragPane ()) l1 l2 a (*//**) :: (Read a, Eq a, LayoutClass l1 a, LayoutClass l2 a) => l1 a -> l2 a -> CombineTwo (DragPane ()) l1 l2 a (*|*) :: (Read a, Eq a, LayoutClass l1 a, LayoutClass l2 a) => l1 a -> l2 a -> CombineTwo (Tall ()) l1 l2 a (**|*) :: (Read a, Eq a, LayoutClass l1 a, LayoutClass l2 a) => l1 a -> l2 a -> CombineTwo (Tall ()) l1 l2 a (***|*) :: (Read a, Eq a, LayoutClass l1 a, LayoutClass l2 a) => l1 a -> l2 a -> CombineTwo (Tall ()) l1 l2 a (****|*) :: (Read a, Eq a, LayoutClass l1 a, LayoutClass l2 a) => l1 a -> l2 a -> CombineTwo (Tall ()) l1 l2 a (***|**) :: (Read a, Eq a, LayoutClass l1 a, LayoutClass l2 a) => l1 a -> l2 a -> CombineTwo (Tall ()) l1 l2 a (****|***) :: (Read a, Eq a, LayoutClass l1 a, LayoutClass l2 a) => l1 a -> l2 a -> CombineTwo (Tall ()) l1 l2 a (***|****) :: (Read a, Eq a, LayoutClass l1 a, LayoutClass l2 a) => l1 a -> l2 a -> CombineTwo (Tall ()) l1 l2 a (*|****) :: (Read a, Eq a, LayoutClass l1 a, LayoutClass l2 a) => l1 a -> l2 a -> CombineTwo (Tall ()) l1 l2 a (**|***) :: (Read a, Eq a, LayoutClass l1 a, LayoutClass l2 a) => l1 a -> l2 a -> CombineTwo (Tall ()) l1 l2 a (*|***) :: (Read a, Eq a, LayoutClass l1 a, LayoutClass l2 a) => l1 a -> l2 a -> CombineTwo (Tall ()) l1 l2 a (*|**) :: (Read a, Eq a, LayoutClass l1 a, LayoutClass l2 a) => l1 a -> l2 a -> CombineTwo (Tall ()) l1 l2 a (*/*) :: (Read a, Eq a, LayoutClass l1 a, LayoutClass l2 a) => l1 a -> l2 a -> CombineTwo (Mirror Tall ()) l1 l2 a (**/*) :: (Read a, Eq a, LayoutClass l1 a, LayoutClass l2 a) => l1 a -> l2 a -> CombineTwo (Mirror Tall ()) l1 l2 a (***/*) :: (Read a, Eq a, LayoutClass l1 a, LayoutClass l2 a) => l1 a -> l2 a -> CombineTwo (Mirror Tall ()) l1 l2 a (****/*) :: (Read a, Eq a, LayoutClass l1 a, LayoutClass l2 a) => l1 a -> l2 a -> CombineTwo (Mirror Tall ()) l1 l2 a (***/**) :: (Read a, Eq a, LayoutClass l1 a, LayoutClass l2 a) => l1 a -> l2 a -> CombineTwo (Mirror Tall ()) l1 l2 a (****/***) :: (Read a, Eq a, LayoutClass l1 a, LayoutClass l2 a) => l1 a -> l2 a -> CombineTwo (Mirror Tall ()) l1 l2 a (***/****) :: (Read a, Eq a, LayoutClass l1 a, LayoutClass l2 a) => l1 a -> l2 a -> CombineTwo (Mirror Tall ()) l1 l2 a (*/****) :: (Read a, Eq a, LayoutClass l1 a, LayoutClass l2 a) => l1 a -> l2 a -> CombineTwo (Mirror Tall ()) l1 l2 a (**/***) :: (Read a, Eq a, LayoutClass l1 a, LayoutClass l2 a) => l1 a -> l2 a -> CombineTwo (Mirror Tall ()) l1 l2 a (*/***) :: (Read a, Eq a, LayoutClass l1 a, LayoutClass l2 a) => l1 a -> l2 a -> CombineTwo (Mirror Tall ()) l1 l2 a (*/**) :: (Read a, Eq a, LayoutClass l1 a, LayoutClass l2 a) => l1 a -> l2 a -> CombineTwo (Mirror Tall ()) l1 l2 a -- | A reimplementation of the combinator of the same name from the xmonad -- core, providing layout choice, and the ability to support -- JumpToLayout messages. (|||) :: (LayoutClass l1 a, LayoutClass l2 a) => l1 a -> l2 a -> NewSelect l1 l2 a data JumpToLayout -- | A message to jump to a particular layout , specified by its -- description string.. JumpToLayout :: String -> JumpToLayout NextLayoutNoWrap :: JumpToLayout Wrap :: JumpToLayout data NewSelect l1 l2 a instance GHC.Show.Show XMonad.Layout.LayoutCombinators.JumpToLayout instance GHC.Read.Read XMonad.Layout.LayoutCombinators.JumpToLayout instance (GHC.Show.Show (l1 a), GHC.Show.Show (l2 a)) => GHC.Show.Show (XMonad.Layout.LayoutCombinators.NewSelect l1 l2 a) instance (GHC.Read.Read (l1 a), GHC.Read.Read (l2 a)) => GHC.Read.Read (XMonad.Layout.LayoutCombinators.NewSelect l1 l2 a) instance XMonad.Core.Message XMonad.Layout.LayoutCombinators.JumpToLayout instance (XMonad.Core.LayoutClass l1 a, XMonad.Core.LayoutClass l2 a) => XMonad.Core.LayoutClass (XMonad.Layout.LayoutCombinators.NewSelect l1 l2) a -- | This module allows to cycle through the given subset of layouts. module XMonad.Actions.CycleSelectedLayouts -- | If the current layout is in the list, cycle to the next layout. -- Otherwise, apply the first layout from list. cycleThroughLayouts :: [String] -> X () -- | This module specifies my xmonad defaults. module XMonad.Config.Arossato arossatoConfig :: MonadIO m => m (XConfig (ModifiedLayout AvoidStruts (NewSelect (ModifiedLayout (Decoration SimpleDecoration DefaultShrinker) (ModifiedLayout MouseResize (ModifiedLayout WindowArranger SimpleFloat))) (NewSelect (ModifiedLayout WithBorder (ModifiedLayout (Decoration TabbedDecoration DefaultShrinker) Simplest)) (ModifiedLayout WindowArranger (NewSelect (ModifiedLayout Magnifier Tall) (NewSelect (ModifiedLayout WithBorder Full) (NewSelect (Mirror Tall) Accordion)))))))) -- | A layout-selection prompt for XMonad module XMonad.Prompt.Layout layoutPrompt :: XPConfig -> X () module XMonad.Config.Droundy config :: XConfig (ModifiedLayout ShowWName (ModifiedLayout WorkspaceDir (ModifiedLayout BoringWindows (ModifiedLayout SmartBorder (ModifiedLayout WindowNavigation (ModifiedLayout Magnifier (ToggleLayouts Full (ModifiedLayout AvoidStruts (NewSelect (ModifiedLayout Rename (ModifiedLayout (Decoration TabbedDecoration CustomShrink) Simplest)) (NewSelect (ModifiedLayout Rename (CombineTwo (DragPane ()) (ModifiedLayout (Decoration TabbedDecoration CustomShrink) Simplest) (CombineTwo (Square ()) (ModifiedLayout (Decoration TabbedDecoration CustomShrink) Simplest) (ModifiedLayout (Decoration TabbedDecoration CustomShrink) Simplest)))) (NewSelect (ModifiedLayout Rename (CombineTwo (DragPane ()) (ModifiedLayout (Decoration TabbedDecoration CustomShrink) Simplest) (CombineTwo (DragPane ()) (ModifiedLayout (Decoration TabbedDecoration CustomShrink) Simplest) (CombineTwo (Square ()) (ModifiedLayout (Decoration TabbedDecoration CustomShrink) Simplest) (ModifiedLayout (Decoration TabbedDecoration CustomShrink) Simplest))))) (ModifiedLayout Rename (CombineTwo (DragPane ()) (CombineTwo (DragPane ()) (ModifiedLayout (Decoration TabbedDecoration CustomShrink) Simplest) (ModifiedLayout (Decoration TabbedDecoration CustomShrink) Simplest)) (CombineTwo (Square ()) (ModifiedLayout (Decoration TabbedDecoration CustomShrink) Simplest) (ModifiedLayout (Decoration TabbedDecoration CustomShrink) Simplest))))))))))))))) mytab :: ModifiedLayout (Decoration TabbedDecoration CustomShrink) Simplest Window instance XMonad.Layout.Decoration.Shrinker XMonad.Layout.Decoration.CustomShrink -- | Example layouts for XMonad.Layout.Groups. module XMonad.Layout.Groups.Examples rowOfColumns :: Groups (ModifiedLayout Rename (Mirror (ZoomRow ClassEQ))) (ZoomRow GroupEQ) Window -- | Increase the width of the focused column zoomColumnIn :: X () -- | Decrease the width of the focused column zoomColumnOut :: X () -- | Reset the width of the focused column zoomColumnReset :: X () -- | Toggle whether the currently focused column should take up all -- available space whenever it has focus toggleColumnFull :: X () -- | Increase the heigth of the focused window zoomWindowIn :: X () -- | Decrease the height of the focused window zoomWindowOut :: X () -- | Reset the height of the focused window zoomWindowReset :: X () -- | Toggle whether the currently focused window should take up the whole -- column whenever it has focus toggleWindowFull :: X () tallTabs :: Shrinker s => TiledTabsConfig s -> ModifiedLayout Rename (ModifiedLayout (Decoration TabbedDecoration s) (Groups (ModifiedLayout Rename Simplest) (NewSelect (ModifiedLayout Rename Tall) (NewSelect (ModifiedLayout Rename (Mirror Tall)) Full)))) Window mirrorTallTabs :: Shrinker s => TiledTabsConfig s -> ModifiedLayout Rename (ModifiedLayout (Decoration TabbedDecoration s) (Groups (ModifiedLayout Rename Simplest) (NewSelect (ModifiedLayout Rename (Mirror Tall)) (NewSelect Full (ModifiedLayout Rename Tall))))) Window fullTabs :: Shrinker s => TiledTabsConfig s -> ModifiedLayout Rename (ModifiedLayout (Decoration TabbedDecoration s) (Groups (ModifiedLayout Rename Simplest) (NewSelect Full (NewSelect (ModifiedLayout Rename Tall) (ModifiedLayout Rename (Mirror Tall)))))) Window -- | Configuration data for the "tiled tab groups" layout data TiledTabsConfig s TTC :: Int -> Rational -> Rational -> Int -> Rational -> Rational -> s -> Theme -> TiledTabsConfig s [vNMaster] :: TiledTabsConfig s -> Int [vRatio] :: TiledTabsConfig s -> Rational [vIncrement] :: TiledTabsConfig s -> Rational [hNMaster] :: TiledTabsConfig s -> Int [hRatio] :: TiledTabsConfig s -> Rational [hIncrement] :: TiledTabsConfig s -> Rational [tabsShrinker] :: TiledTabsConfig s -> s [tabsTheme] :: TiledTabsConfig s -> Theme -- | The default value for this type. def :: Default a => a -- | Deprecated: Use def (from Data.Default, and re-exported by -- XMonad.Layout.Groups) instead. defaultTiledTabsConfig :: TiledTabsConfig DefaultShrinker -- | Increase the number of master groups by one increaseNMasterGroups :: X () -- | Decrease the number of master groups by one decreaseNMasterGroups :: X () -- | Shrink the master area shrinkMasterGroups :: X () -- | Expand the master area expandMasterGroups :: X () -- | Rotate the available outer layout algorithms nextOuterLayout :: X () shrinkText :: DefaultShrinker -- | The default xmonad Theme. -- | Deprecated: Use def (from Data.Default, and re-exported by -- XMonad.Layout.Decoration) instead. defaultTheme :: Theme -- | Compare two Groups by comparing the ids of their layouts. data GroupEQ a GroupEQ :: GroupEQ a zoomRowG :: (Eq a, Show a, Read a, Show (l a), Read (l a)) => ZoomRow GroupEQ (Group l a) instance GHC.Read.Read (XMonad.Layout.Groups.Examples.GroupEQ a) instance GHC.Show.Show (XMonad.Layout.Groups.Examples.GroupEQ a) instance GHC.Classes.Eq a => XMonad.Layout.ZoomRow.EQF XMonad.Layout.Groups.Examples.GroupEQ (XMonad.Layout.Groups.Group l a) instance (s ~ XMonad.Layout.Decoration.DefaultShrinker) => Data.Default.Class.Default (XMonad.Layout.Groups.Examples.TiledTabsConfig s) -- | A wmii-like layout algorithm. module XMonad.Layout.Groups.Wmii -- | A layout inspired by wmii wmii :: Shrinker s => s -> Theme -> Groups (ModifiedLayout Rename (ModifiedLayout (Decoration TabbedDecoration s) (Ignore ChangeLayout (Ignore JumpToLayout (ModifiedLayout UnEscape (NewSelect (ModifiedLayout Rename Tall) (NewSelect (ModifiedLayout Rename Simplest) Full))))))) (ZoomRow GroupEQ) Window -- | Increase the width of the focused group zoomGroupIn :: X () -- | Decrease the size of the focused group zoomGroupOut :: X () -- | Reset the size of the focused group to the default zoomGroupReset :: X () -- | Toggle whether the currently focused group should be maximized -- whenever it has focus. toggleGroupFull :: X () -- | Rotate the layouts in the focused group. groupToNextLayout :: X () -- | Switch the focused group to the "maximized" layout. groupToFullLayout :: X () -- | Switch the focused group to the "tabbed" layout. groupToTabbedLayout :: X () -- | Switch the focused group to the "column" layout. groupToVerticalLayout :: X () shrinkText :: DefaultShrinker -- | The default value for this type. def :: Default a => a -- | The default xmonad Theme. -- | Deprecated: Use def (from Data.Default, and re-exported by -- XMonad.Layout.Decoration) instead. defaultTheme :: Theme -- | This is a list of selected commands that can be made available using -- XMonad.Hooks.ServerMode to allow external programs to control -- the window manager. Bluetile -- (http://projects.haskell.org/bluetile/) uses this to enable its -- dock application to do things like changing workspaces and layouts. module XMonad.Actions.BluetileCommands bluetileCommands :: X [(String, X ())] -- | This is the default configuration of Bluetile -- (http://projects.haskell.org/bluetile/). If you are migrating -- from Bluetile to xmonad or want to create a similar setup, then this -- will give you pretty much the same thing, except for Bluetile's helper -- applications such as the dock. module XMonad.Config.Bluetile bluetileConfig :: XConfig (ModifiedLayout AvoidStruts (ModifiedLayout Minimize (ModifiedLayout BoringWindows (NewSelect (ModifiedLayout Rename (ModifiedLayout (Decoration ButtonDecoration DefaultShrinker) (ModifiedLayout Maximize (ModifiedLayout BorderResize PositionStoreFloat)))) (NewSelect (ModifiedLayout Rename (ModifiedLayout (Decoration WindowSwitcherDecoration DefaultShrinker) (ModifiedLayout DraggingVisualizer (ModifiedLayout Maximize MouseResizableTile)))) (NewSelect (ModifiedLayout Rename (ModifiedLayout (Decoration WindowSwitcherDecoration DefaultShrinker) (ModifiedLayout DraggingVisualizer (ModifiedLayout Maximize MouseResizableTile)))) (ModifiedLayout Rename (ModifiedLayout (Decoration WindowSwitcherDecoration DefaultShrinker) (ModifiedLayout DraggingVisualizer (ModifiedLayout Maximize (ModifiedLayout SmartBorder Full))))))))))) -- | Perform an action after the current mouse drag is completed. module XMonad.Actions.AfterDrag -- | Schedule a task to take place after the current dragging is completed. afterDrag :: X () -> X () -- | Take an action if the current dragging can be considered a click, -- supposing the drag just started before this function is called. A drag -- is considered a click if it is completed within 300 ms. ifClick :: X () -> X () -- | Take an action if the current dragging is completed within a certain -- time (in milliseconds.) ifClick' :: Int -> X () -> X () -> X () -- | Move and resize floating windows using other windows and the edge of -- the screen as guidelines. module XMonad.Actions.FloatSnap -- | Two-dimensional directions: data Direction2D -- | Up U :: Direction2D -- | Down D :: Direction2D -- | Right R :: Direction2D -- | Left L :: Direction2D -- | Move a window in the specified direction until it snaps against -- another window or the edge of the screen. snapMove :: Direction2D -> Maybe Int -> Window -> X () -- | Grow the specified edge of a window until it snaps against another -- window or the edge of the screen. snapGrow :: Direction2D -> Maybe Int -> Window -> X () -- | Shrink the specified edge of a window until it snaps against another -- window or the edge of the screen. snapShrink :: Direction2D -> Maybe Int -> Window -> X () -- | Move a window by both axises in any direction to snap against the -- closest part of other windows or the edge of the screen. snapMagicMove :: Maybe Int -> Maybe Int -> Window -> X () -- | Resize the window by each edge independently to snap against the -- closest part of other windows or the edge of the screen. snapMagicResize :: [Direction2D] -> Maybe Int -> Maybe Int -> Window -> X () -- | Resize the window by each edge independently to snap against the -- closest part of other windows or the edge of the screen. Use the -- location of the mouse over the window to decide which edges to snap. -- In corners, the two adjoining edges will be snapped, along the middle -- of an edge only that edge will be snapped. In the center of the window -- all edges will snap. Intended to be used together with -- XMonad.Actions.FlexibleResize or -- XMonad.Actions.FlexibleManipulate. snapMagicMouseResize :: Rational -> Maybe Int -> Maybe Int -> Window -> X () -- | Schedule a task to take place after the current dragging is completed. afterDrag :: X () -> X () -- | Take an action if the current dragging can be considered a click, -- supposing the drag just started before this function is called. A drag -- is considered a click if it is completed within 300 ms. ifClick :: X () -> X () -- | Take an action if the current dragging is completed within a certain -- time (in milliseconds.) ifClick' :: Int -> X () -> X () -> X () -- | This module gives a brief overview of the xmonad internals. It is -- intended for advanced users who are curious about the xmonad source -- code and want an brief overview. This document may also be helpful for -- the beginner/intermediate Haskell programmer who is motivated to write -- an xmonad extension as a way to deepen her understanding of this -- powerful functional language; however, there is not space here to go -- into much detail. For a more comprehensive document covering some of -- the same material in more depth, see the guided tour of the xmonad -- source on the xmonad wiki: -- http://haskell.org/haskellwiki/Xmonad/Guided_tour_of_the_xmonad_source. -- -- If you write an extension module and think it may be useful for -- others, consider releasing it. Coding guidelines and licensing -- policies are covered at the end of this document, and must be followed -- if you want your code to be included in the official repositories. For -- a basic tutorial on the nuts and bolts of developing a new extension -- for xmonad, see the tutorial on the wiki: -- http://haskell.org/haskellwiki/Xmonad/xmonad_development_tutorial. module XMonad.Doc.Developing -- | This module documents the xmonad-contrib library and how to use it to -- extend the capabilities of xmonad. -- -- Reading this document should not require a deep knowledge of Haskell; -- the examples are intended to be useful and understandable for those -- users who do not know Haskell and don't want to have to learn it just -- to configure xmonad. You should be able to get by just fine by -- ignoring anything you don't understand and using the provided examples -- as templates. However, relevant Haskell features are discussed when -- appropriate, so this document will hopefully be useful for more -- advanced Haskell users as well. -- -- Those wishing to be totally hardcore and develop their own xmonad -- extensions (it's easier than it sounds, we promise!) should read the -- documentation in XMonad.Doc.Developing. -- -- More configuration examples may be found on the Haskell wiki: -- -- http://haskell.org/haskellwiki/Xmonad/Config_archive module XMonad.Doc.Extending -- | This is a brief tutorial that will teach you how to create a basic -- xmonad configuration. -- -- For more detailed instructions on extending xmonad with the -- xmonad-contrib library, see XMonad.Doc.Extending. module XMonad.Doc.Configuring -- | This is the main documentation module for the xmonad-contrib library. -- It provides a brief overview of xmonad and a link to documentation for -- configuring and extending xmonad. -- -- A link to documentation describing xmonad internals is also provided. -- This module is mainly intended for those wanting to contribute code, -- or for those who are curious to know what's going on behind the -- scenes. module XMonad.Doc