[xmonad] Toggle Magnification

aditya siram aditya.siram at gmail.com
Mon Jan 5 14:46:28 EST 2009


I am trying to get maximization working with the MultiToggle module but
Xmonad keeps crashing.

Here is the layout and keybinding section of my conf file:
>mylayoutHook = mkToggle (single FULL) ( Grid False ||| Accordion |||
ResizableTall 1 (3/100) (1/2) [] ||| tabbed shrinkText defaultTheme)
>keysToAdd x = [((modMask x, xK_m), sendMessage $ Toggle FULL)]

I can reproduce the problem by doing the following. Start Xmonad (starts off
in Grid mode). Then `Alt-Space` to toggle Accordion, ResizableTall, tabbed,
and back to Grid. `Alt-Space` again and the X server crashes.

Here is my entire xmonad.hs file:
import XMonad
import XMonad.Layout
import XMonad.Layout.Tabbed
import XMonad.Layout.Accordion
import XMonad.Layout.NoBorders
import XMonad.Layout.HintedGrid
import XMonad.Layout.ResizableTile
import XMonad.Layout.ShowWName
import XMonad.Layout.MultiToggle
import XMonad.Layout.MultiToggle.Instances
import Data.Map as M

-- mylayoutHook = tabbed shrinkText defaultTheme ||| Accordion |||
ResizableTall 1 (3/100) (1/2) []
mylayoutHook = mkToggle (single FULL) ( Grid False ||| Accordion |||
ResizableTall 1 (3/100) (1/2) [] ||| tabbed shrinkText defaultTheme)
newKeys x =
    let initial_ks = XMonad.keys defaultConfig x
    in
      add $ remove $ initial_ks
          where remove ks = M.difference ks (M.fromList $ keysToRemove x)
                add    ks = M.union      ks (M.fromList $ keysToAdd    x)
keysToRemove :: XConfig Layout ->    [((KeyMask, KeySym),X ())]
keysToRemove x = [((modMask x, xK_p ), return ()),((modMask x, xK_b), return
()), ((modMask x, xK_n), return ())]
keysToAdd :: XConfig Layout ->    [((KeyMask, KeySym),X ())]
keysToAdd x = [((modMask x, xK_m), sendMessage $ Toggle FULL)]
main = xmonad $ defaultConfig { XMonad.keys = newKeys, layoutHook =
showWName mylayoutHook }

Thanks for your help ...
-deech



On Mon, Jan 5, 2009 at 1:11 PM, Richard Riley <rileyrgdev at googlemail.com>wrote:

>
> "aditya siram" <aditya.siram at gmail.com> writes:
>
> > Hi all,
> > I would like to maximize my focused window. There are three modules in
> the
> > Xmonad-contrib library : XMonad.Layout.Magnifier, XMonad.Layout.Maximize,
> > XMonad.Layout.MultiToggle. They all appear to implement maximizing.
> >
> > Any recommendations?
>
> You might consider using toggle full.
>  e.g
>
>   myCommonLayouts =  ewmhDesktopsLayout  $ avoidStruts $ (toggleLayouts
> Full Circle)  ||| (toggleLayouts Full tiled) ||| Mirror (toggleLayouts  Full
> (TwoPane (3/100) (1/2)))
>    where
>      tiled = Tall nmaster delta ratio
>      nmaster = 1
>      delta = 3/100
>      ratio = 1/2
>
> and
>
>       ,((modMask(myConfig), xK_f), sendMessage ToggleLayout)
>
>
> >
> > -deech
> > Hi all,
> > I would like to maximize my focused window. There are three modules in
> the Xmonad-contrib library :
> > XMonad.Layout.Magnifier, XMonad.Layout.Maximize,
> XMonad.Layout.MultiToggle. They all appear to implement maximizing.
> >
> > Any recommendations?
> >
> > -deech
> >
> > _______________________________________________
> > xmonad mailing list
> > xmonad at haskell.org
> > http://www.haskell.org/mailman/listinfo/xmonad
>
> --
>  important and urgent problems of the technology of today are no longer the
> satisfactions of the primary needs or of archetypal wishes, but the
> reparation of the evils and damages by the technology of yesterday.  ~Dennis
> Gabor, Innovations:  Scientific, Technological and Social, 1970
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/xmonad/attachments/20090105/17d52e80/attachment.htm


More information about the xmonad mailing list