How to organize myLayoutHook?

Most parts of my xmonad.hs have reasonably simple types: myXPConfig :: XPConfig myKeys :: XConfig Layout -> M.Map (KeyMask, KeySym) (X ()) myManageHook :: ManageHook myLogHook :: Handle -> X () myWorkspaces :: [WorkspaceId] etc. But myLayoutHook is uniquely complicated. Here's the current version: myLayoutHook = avoidStruts $ smartBorders $ onWorkspace "4:gimp" gimp $ modWorkspace "1:admin" (workspaceDir "~/dotfiles") $ all where all = Full ||| tall ||| Grid ||| wide tall = named "tall" $ FixedColumn 1 20 80 10 wide = named "wide" $ Mirror $ tall gimp = named "gimp" $ withIM (0.15) (Role "gimp-toolbox") $ reflectHoriz $ withIM (0.25) (Role "gimp-dock") $ all And here's its type: myLayoutHook :: XMonad.Layout.LayoutModifier.ModifiedLayout AvoidStruts (XMonad.Layout.LayoutModifier.ModifiedLayout SmartBorder (PerWorkspace (XMonad.Layout.LayoutModifier.ModifiedLayout XMonad.Layout.Renamed.Rename (XMonad.Layout.LayoutModifier.ModifiedLayout AddRoster (XMonad.Layout.LayoutModifier.ModifiedLayout Reflect (XMonad.Layout.LayoutModifier.ModifiedLayout AddRoster (NewSelect Full (NewSelect (XMonad.Layout.LayoutModifier.ModifiedLayout XMonad.Layout.Renamed.Rename FixedColumn) (NewSelect Grid (XMonad.Layout.LayoutModifier.ModifiedLayout XMonad.Layout.Renamed.Rename (Mirror (XMonad.Layout.LayoutModifier.ModifiedLayout XMonad.Layout.Renamed.Rename FixedColumn)))))))))) (PerWorkspace (XMonad.Layout.LayoutModifier.ModifiedLayout WorkspaceDir (NewSelect Full (NewSelect (XMonad.Layout.LayoutModifier.ModifiedLayout XMonad.Layout.Renamed.Rename FixedColumn) (NewSelect Grid (XMonad.Layout.LayoutModifier.ModifiedLayout XMonad.Layout.Renamed.Rename (Mirror (XMonad.Layout.LayoutModifier.ModifiedLayout XMonad.Layout.Renamed.Rename FixedColumn))))))) (NewSelect Full (NewSelect (XMonad.Layout.LayoutModifier.ModifiedLayout XMonad.Layout.Renamed.Rename FixedColumn) (NewSelect Grid (XMonad.Layout.LayoutModifier.ModifiedLayout XMonad.Layout.Renamed.Rename (Mirror (XMonad.Layout.LayoutModifier.ModifiedLayout XMonad.Layout.Renamed.Rename FixedColumn))))))))) Window Can that be simplified at all? I find myself wanting to add more workspace-specific rules, like workspaceDirs or different layouts, but the changes are hard to reason about and always seem to break something. Thanks Jeff

On 16 October 2012 23:38, Jeffrey David Johnson
Most parts of my xmonad.hs have reasonably simple types:
myXPConfig :: XPConfig myKeys :: XConfig Layout -> M.Map (KeyMask, KeySym) (X ()) myManageHook :: ManageHook myLogHook :: Handle -> X () myWorkspaces :: [WorkspaceId] etc.
But myLayoutHook is uniquely complicated. Here's the current version:
myLayoutHook = avoidStruts $ smartBorders $ onWorkspace "4:gimp" gimp $ modWorkspace "1:admin" (workspaceDir "~/dotfiles") $ all
where all = Full ||| tall ||| Grid ||| wide
tall = named "tall" $ FixedColumn 1 20 80 10 wide = named "wide" $ Mirror $ tall gimp = named "gimp" $ withIM (0.15) (Role "gimp-toolbox") $ reflectHoriz $ withIM (0.25) (Role "gimp-dock") $ all
I don't find your layout specially complicated...
And here's its type:
myLayoutHook :: XMonad.Layout.LayoutModifier.ModifiedLayout AvoidStruts (XMonad.Layout.LayoutModifier.ModifiedLayout SmartBorder (PerWorkspace (XMonad.Layout.LayoutModifier.ModifiedLayout XMonad.Layout.Renamed.Rename (XMonad.Layout.LayoutModifier.ModifiedLayout AddRoster (XMonad.Layout.LayoutModifier.ModifiedLayout Reflect (XMonad.Layout.LayoutModifier.ModifiedLayout AddRoster (NewSelect Full (NewSelect (XMonad.Layout.LayoutModifier.ModifiedLayout XMonad.Layout.Renamed.Rename FixedColumn) (NewSelect Grid (XMonad.Layout.LayoutModifier.ModifiedLayout XMonad.Layout.Renamed.Rename (Mirror (XMonad.Layout.LayoutModifier.ModifiedLayout XMonad.Layout.Renamed.Rename FixedColumn)))))))))) (PerWorkspace (XMonad.Layout.LayoutModifier.ModifiedLayout WorkspaceDir (NewSelect Full (NewSelect (XMonad.Layout.LayoutModifier.ModifiedLayout XMonad.Layout.Renamed.Rename FixedColumn) (NewSelect Grid (XMonad.Layout.LayoutModifier.ModifiedLayout XMonad.Layout.Renamed.Rename (Mirror (XMonad.Layout.LayoutModifier.ModifiedLayout XMonad.Layout.Renamed.Rename FixedColumn))))))) (NewSelect Full (NewSelect (XMonad.Layout.LayoutModifier.ModifiedLayout XMonad.Layout.Renamed.Rename FixedColumn) (NewSelect Grid (XMonad.Layout.LayoutModifier.ModifiedLayout XMonad.Layout.Renamed.Rename (Mirror (XMonad.Layout.LayoutModifier.ModifiedLayout XMonad.Layout.Renamed.Rename FixedColumn))))))))) Window
Can that be simplified at all? I find myself wanting to add more workspace-specific rules, like workspaceDirs or different layouts, but the changes are hard to reason about and always seem to break something.
I'm a newbie on xmonad, and a totally noob on haskell, but I haven't seen a single layouthook in a lot of (important) xmonad configs around the web that holds a type. Prolly for the same reason you are stating. Regards, -- Pablo Olmos de Aguilera Corradini - @PaBLoX http://www.glatelier.org/ http://about.me/pablox/ http://www.linkedin.com/in/pablooda/ Linux User: #456971 - http://counter.li.org/

On Tue, Oct 16, 2012 at 11:47 PM, Pablo Olmos de Aguilera C. < pablo@glatelier.org> wrote:
I'm a newbie on xmonad, and a totally noob on haskell, but I haven't seen a single layouthook in a lot of (important) xmonad configs around the web that holds a type. Prolly for the same reason you are stating.
Pretty much, yes. You can find some explicitly typed layouts in XMonadContrib, and yes, they get complex pretty quickly. It's almost always best to let the type be inferred. -- brandon s allbery kf8nh sine nomine associates allbery.b@gmail.com ballbery@sinenomine.net unix/linux, openafs, kerberos, infrastructure http://sinenomine.net

Hi David, On Tue, Oct 16, 2012 at 07:38:22PM -0700, Jeffrey David Johnson wrote:
Most parts of my xmonad.hs have reasonably simple types:
myXPConfig :: XPConfig myKeys :: XConfig Layout -> M.Map (KeyMask, KeySym) (X ()) myManageHook :: ManageHook myLogHook :: Handle -> X () myWorkspaces :: [WorkspaceId] etc.
But myLayoutHook is uniquely complicated. Here's the current version: ...
Partly it seems to be because of the Choose type in 'xmonad/XMonad/Layout.hs', which is used in a recursive manner to combine the layouts (|||). I think it's done this way to be able to combine different layout types, which all have an instance of LayoutClass, without needing existential quantification. By using existential quantification it might be possible to represent the combined layouts by just a list, and the current layout could be indicated by a lens. Or I'm missing something regarding the Choose type? Greetings, Daniel

Thanks, that's good to know I'm doing things generally right. Maybe a more specific question would help me improve it though... what I'm actually trying to do is make a tabular list of workspace properties like this: myLayoutHook = avoidStruts $ smartBorders $ format [ ("admin", "~/dotfiles", (Full, tall, Grid, wide)) , ("notes" , "~/notes" , (tall, wide) ) ] where tall = ... wide = ... format = ??? And I can't figure out what the format function should be. Jeff On 10/16/12 23:11, Daniel Trstenjak wrote:
Hi David,
On Tue, Oct 16, 2012 at 07:38:22PM -0700, Jeffrey David Johnson wrote:
Most parts of my xmonad.hs have reasonably simple types:
myXPConfig :: XPConfig myKeys :: XConfig Layout -> M.Map (KeyMask, KeySym) (X ()) myManageHook :: ManageHook myLogHook :: Handle -> X () myWorkspaces :: [WorkspaceId] etc.
But myLayoutHook is uniquely complicated. Here's the current version: ... Partly it seems to be because of the Choose type in 'xmonad/XMonad/Layout.hs', which is used in a recursive manner to combine the layouts (|||).
I think it's done this way to be able to combine different layout types, which all have an instance of LayoutClass, without needing existential quantification.
By using existential quantification it might be possible to represent the combined layouts by just a list, and the current layout could be indicated by a lens.
Or I'm missing something regarding the Choose type?
Greetings, Daniel
_______________________________________________ xmonad mailing list xmonad@haskell.org http://www.haskell.org/mailman/listinfo/xmonad

On Tue, Oct 16, 2012 at 11:38:13PM -0700, Jeffrey David Johnson wrote:
Thanks, that's good to know I'm doing things generally right. Maybe a more specific question would help me improve it though... what I'm actually trying to do is make a tabular list of workspace properties like this:
myLayoutHook = avoidStruts $ smartBorders $ format [ ("admin", "~/dotfiles", (Full, tall, Grid, wide)) , ("notes" , "~/notes" , (tall, wide) ) ] where tall = ... wide = ... format = ???
And I can't figure out what the format function should be. Jeff
Perhaps something like (didn't test it): myLayoutHook = avoidStruts $ smartBorders $ format [ ("admin", "~/dotfiles", Full ||| tall ||| Grid ||| wide) , ("notes" , "~/notes" , tall ||| wide) ] where tall = ... wide = ... defaultWorkspace = tall ||| wide -- or whatever format (w:[]) = workspace w format (w:ws) = workspace w ||| format ws workspace (name, dir, layouts) = onWorkspace name layouts defaultWorkspace ||| modWorkspace name (workspaceDir dir) defaultWorkspace Greetings, Daniel

On Wed, Oct 17, 2012 at 09:34:06AM +0200, Daniel Trstenjak wrote:
format (w:[]) = workspace w format (w:ws) = workspace w ||| format ws
workspace (name, dir, layouts) = onWorkspace name layouts defaultWorkspace ||| modWorkspace name (workspaceDir dir) defaultWorkspace
Wait, I think the usage of ||| is wrong here, because it would result in more layouts than you want. So it should be more something like (again, without testing): format (w:[]) = workspace w defaultWorkspace format (w:ws) = workspace w $ format ws workspace (name, dir, layouts) = onWorkspace name layouts $ modWorkspace name (workspaceDir dir) Greetings, Daniel

Hm I wasn't able to get it to work, though I'm not sure why. It looks like it should. Actual code: myLayoutHook = avoidStruts $ smartBorders $ format [ ("admin", "~/dotfiles", base ) , ("notes", "~/notes" , tall ||| wide) ] where format (w:[]) = workspace w base format (w:ws) = workspace w $ format ws workspace (n,d,l) = onWorkspace n l $ modWorkspace n (workspaceDir d) base = Full ||| tall ||| Grid ||| wide tall = named "tall" $ FixedColumn 1 20 80 10 wide = named "wide" $ Mirror $ tall gimp = named "gimp" $ withIM (0.15) (Role "gimp-toolbox") $ reflectHoriz $ withIM (0.25) (Role "gimp-dock") $ base And the resulting error: xmonad.hs:43:40: Couldn't match type `XMonad.Layout.LayoutModifier.ModifiedLayout XMonad.Layout.Renamed.Rename FixedColumn' with `Full' Expected type: Full a0 Actual type: XMonad.Layout.LayoutModifier.ModifiedLayout XMonad.Layout.Renamed.Rename FixedColumn a0 In the first argument of `(|||)', namely `tall' In the expression: tall ||| wide In the expression: ("notes", "~/notes", tall ||| wide) xmonad.hs:43:49: Couldn't match type `XMonad.Layout.LayoutModifier.ModifiedLayout XMonad.Layout.Renamed.Rename (Mirror (XMonad.Layout.LayoutModifier.ModifiedLayout XMonad.Layout.Renamed.Rename FixedColumn))' with `NewSelect (XMonad.Layout.LayoutModifier.ModifiedLayout XMonad.Layout.Renamed.Rename FixedColumn) (NewSelect Grid (XMonad.Layout.LayoutModifier.ModifiedLayout XMonad.Layout.Renamed.Rename (Mirror (XMonad.Layout.LayoutModifier.ModifiedLayout XMonad.Layout.Renamed.Rename FixedColumn))))' Expected type: NewSelect (XMonad.Layout.LayoutModifier.ModifiedLayout XMonad.Layout.Renamed.Rename FixedColumn) (NewSelect Grid (XMonad.Layout.LayoutModifier.ModifiedLayout XMonad.Layout.Renamed.Rename (Mirror (XMonad.Layout.LayoutModifier.ModifiedLayout XMonad.Layout.Renamed.Rename FixedColumn)))) a0 Actual type: XMonad.Layout.LayoutModifier.ModifiedLayout XMonad.Layout.Renamed.Rename (Mirror (XMonad.Layout.LayoutModifier.ModifiedLayout XMonad.Layout.Renamed.Rename FixedColumn)) a0 In the second argument of `(|||)', namely `wide' In the expression: tall ||| wide In the expression: ("notes", "~/notes", tall ||| wide) xmonad.hs:46:25: Couldn't match expected type `NewSelect Full (NewSelect (XMonad.Layout.LayoutModifier.ModifiedLayout XMonad.Layout.Renamed.Rename FixedColumn) (NewSelect Grid (XMonad.Layout.LayoutModifier.ModifiedLayout XMonad.Layout.Renamed.Rename (Mirror (XMonad.Layout.LayoutModifier.ModifiedLayout XMonad.Layout.Renamed.Rename FixedColumn))))) a0 -> t0' with actual type `PerWorkspace l10 ((->) (l0 a1)) (PerWorkspace (XMonad.Layout.LayoutModifier.ModifiedLayout WorkspaceDir l0) l0 a1)' The function `workspace' is applied to two arguments, but its type `(WorkspaceId, String, l10 (PerWorkspace (XMonad.Layout.LayoutModifier.ModifiedLayout WorkspaceDir l0) l0 a1)) -> PerWorkspace l10 ((->) (l0 a1)) (PerWorkspace (XMonad.Layout.LayoutModifier.ModifiedLayout WorkspaceDir l0) l0 a1)' has only one In the expression: workspace w base In an equation for `format': format (w : []) = workspace w base xmonad.hs:47:25: Couldn't match expected type `t0 -> t0' with actual type `PerWorkspace l10 ((->) (l0 a1)) (PerWorkspace (XMonad.Layout.LayoutModifier.ModifiedLayout WorkspaceDir l0) l0 a1)' The first argument of ($) takes one argument, but its type `PerWorkspace l10 ((->) (l0 a1)) (PerWorkspace (XMonad.Layout.LayoutModifier.ModifiedLayout WorkspaceDir l0) l0 a1)' has none In the expression: workspace w $ format ws In an equation for `format': format (w : ws) = workspace w $ format ws I did make some progress in a different direction, with separate lists for each modifier: myLayoutHook = avoidStruts $ smartBorders $ dirs $ layouts where layouts = format ("4:gimp", gimp) $ base where format (a,b) = onWorkspace a b base = Full ||| tall ||| Grid ||| wide tall = named "tall" $ FixedColumn 1 20 80 10 wide = named "wide" $ Mirror $ tall gimp = named "gimp" $ withIM (0.15) (Role "gimp-toolbox") $ reflectHoriz $ withIM (0.25) (Role "gimp-dock") $ base dirs = format ("1:admin" , "~/dotfiles") . format ("2:notes", "~/notes") . base where format (a,b) = modWorkspace a (workspaceDir b) base = workspaceDir "~" The only thing is I wasn't able to make them into actual lists. If I change the last part to: dirs = foldr (.) base $ map format [ ("1:admin", "~/dotfiles") , ("2:notes", "~/notes" ) ] where format (a,b) = modWorkspace a (workspaceDir b) base = workspaceDir "~" This happens: xmonad.hs:59:37: Couldn't match type `PerWorkspace (XMonad.Layout.LayoutModifier.ModifiedLayout WorkspaceDir (XMonad.Layout.LayoutModifier.ModifiedLayout WorkspaceDir l0)) (XMonad.Layout.LayoutModifier.ModifiedLayout WorkspaceDir l0) a0' with `XMonad.Layout.LayoutModifier.ModifiedLayout WorkspaceDir l0 a0' Expected type: (WorkspaceId, String) -> XMonad.Layout.LayoutModifier.ModifiedLayout WorkspaceDir l0 a0 -> XMonad.Layout.LayoutModifier.ModifiedLayout WorkspaceDir l0 a0 Actual type: (WorkspaceId, String) -> XMonad.Layout.LayoutModifier.ModifiedLayout WorkspaceDir l0 a0 -> PerWorkspace (XMonad.Layout.LayoutModifier.ModifiedLayout WorkspaceDir (XMonad.Layout.LayoutModifier.ModifiedLayout WorkspaceDir l0)) (XMonad.Layout.LayoutModifier.ModifiedLayout WorkspaceDir l0) a0 In the first argument of `map', namely `format' In the second argument of `($)', namely `map format [("1:admin", "~/dotfiles"), ("2:notes", "~/notes")]' In the expression: foldr (.) base $ map format [("1:admin", "~/dotfiles"), ("2:notes", "~/notes")] But that's just nitpicking because they're managable as is now. :) Jeff On 10/17/12 00:48, Daniel Trstenjak wrote:
On Wed, Oct 17, 2012 at 09:34:06AM +0200, Daniel Trstenjak wrote:
format (w:[]) = workspace w format (w:ws) = workspace w ||| format ws
workspace (name, dir, layouts) = onWorkspace name layouts defaultWorkspace ||| modWorkspace name (workspaceDir dir) defaultWorkspace
Wait, I think the usage of ||| is wrong here, because it would result in more layouts than you want. So it should be more something like (again, without testing):
format (w:[]) = workspace w defaultWorkspace format (w:ws) = workspace w $ format ws
workspace (name, dir, layouts) = onWorkspace name layouts $ modWorkspace name (workspaceDir dir)
Greetings, Daniel
_______________________________________________ xmonad mailing list xmonad@haskell.org http://www.haskell.org/mailman/listinfo/xmonad

On Wed, Oct 17, 2012 at 09:13:25AM -0700, Jeffrey David Johnson wrote:
xmonad.hs:43:40: Couldn't match type `XMonad.Layout.LayoutModifier.ModifiedLayout XMonad.Layout.Renamed.Rename FixedColumn' with `Full' Expected type: Full a0 Actual type: XMonad.Layout.LayoutModifier.ModifiedLayout XMonad.Layout.Renamed.Rename FixedColumn a0 In the first argument of `(|||)', namely `tall' In the expression: tall ||| wide In the expression: ("notes", "~/notes", tall ||| wide)
I think that's the case, because you can't put different layout types - regardless if they all have an instance of the same type class (LayoutClass) - in the same list, without the usage of existential quantification. I tried this: data AnyLayout a = forall l. (LayoutClass l a) => AnyLayout (l a) test = format [("admin", "~/dotfiles", AnyLayout $ Tall 1 (3/100) (2/3)), ("notes", "~/notes" , AnyLayout $ Full)] where defaultWorkspace = dragPane Vertical 0.1 0.5 format (w:[]) = workspace w $ defaultWorkspace format (w:ws) = workspace w $ format ws workspace (name, dir, AnyLayout l) = onWorkspace name l $ modWorkspace name (workspaceDir dir) But this still results in some compile error, and I don't even know, if it's possible to use existential quantification here. xmonad.hs:79:8: No instance for (LayoutClass ((->) (l0 a0)) (PerWorkspace (XMonad.Layout.LayoutModifier.ModifiedLayout WorkspaceDir l0) l0 a0)) arising from a use of `format' Possible fix: add an instance declaration for (LayoutClass ((->) (l0 a0)) (PerWorkspace (XMonad.Layout.LayoutModifier.ModifiedLayout WorkspaceDir l0) l0 a0)) In the expression: format [("admin", "~/dotfiles", AnyLayout $ Tall 1 (3 / 100) (2 / 3)), ("notes", "~/notes", AnyLayout $ Full)] In an equation for `test': test = format [("admin", "~/dotfiles", AnyLayout $ Tall 1 (3 / 100) (2 / 3)), ("notes", "~/notes", AnyLayout $ Full)] where defaultWorkspace = dragPane Vertical 0.1 0.5 format (w : []) = workspace w $ defaultWorkspace format (w : ws) = workspace w $ format ws workspace (name, dir, AnyLayout l) = onWorkspace name l $ modWorkspace name (workspaceDir dir) xmonad.hs:87:44: Could not deduce (t1 ~ PerWorkspace l1 ((->) (l a)) (PerWorkspace (XMonad.Layout.LayoutModifier.ModifiedLayout WorkspaceDir l) l a)) from the context (LayoutClass l a, LayoutClass ((->) (l a)) (PerWorkspace (XMonad.Layout.LayoutModifier.ModifiedLayout WorkspaceDir l) l a)) bound by the inferred type of workspace :: (LayoutClass l a, LayoutClass ((->) (l a)) (PerWorkspace (XMonad.Layout.LayoutModifier.ModifiedLayout WorkspaceDir l) l a)) => ([Char], [Char], AnyLayout (PerWorkspace (XMonad.Layout.LayoutModifier.ModifiedLayout WorkspaceDir l) l a)) -> t1 at xmonad.hs:87:7-100 or from (LayoutClass l1 (PerWorkspace (XMonad.Layout.LayoutModifier.ModifiedLayout WorkspaceDir l) l a)) bound by a pattern with constructor AnyLayout :: forall a (l :: * -> *). LayoutClass l a => l a -> AnyLayout a, in an equation for `workspace' at xmonad.hs:87:29-39 `t1' is a rigid type variable bound by the inferred type of workspace :: (LayoutClass l a, LayoutClass ((->) (l a)) (PerWorkspace (XMonad.Layout.LayoutModifier.ModifiedLayout WorkspaceDir l) l a)) => ([Char], [Char], AnyLayout (PerWorkspace (XMonad.Layout.LayoutModifier.ModifiedLayout WorkspaceDir l) l a)) -> t1 at xmonad.hs:87:7 In the expression: onWorkspace name l $ modWorkspace name (workspaceDir dir) In an equation for `workspace': workspace (name, dir, AnyLayout l) = onWorkspace name l $ modWorkspace name (workspaceDir dir) In an equation for `test': test = format [("admin", "~/dotfiles", AnyLayout $ Tall 1 (3 / 100) (2 / 3)), ("notes", "~/notes", AnyLayout $ Full)] where defaultWorkspace = dragPane Vertical 0.1 0.5 format (w : []) = workspace w $ defaultWorkspace format (w : ws) = workspace w $ format ws workspace (name, dir, AnyLayout l) = onWorkspace name l $ modWorkspace name (workspaceDir dir) Greetings, Daniel

On Wed, Oct 17, 2012 at 08:11:46AM +0200, Daniel Trstenjak wrote:
By using existential quantification it might be possible to represent the combined layouts by just a list, and the current layout could be indicated by a lens.
Or I'm missing something regarding the Choose type?
Ok, the combined layout has to act and be itself a layout, otherwise you couldn't that easily apply modifiers on the layouts.
participants (4)
-
Brandon Allbery
-
Daniel Trstenjak
-
Jeffrey David Johnson
-
Pablo Olmos de Aguilera C.