
Hi,
I was using 2 screens with xmonad and xmobar.
The settings
ppCurrent = xmobarColor "#CC0000" "" . wrap "[" "]"
, ppVisible = xmobarColor "#EE9A00" "" . wrap "[" "]"
, ppTitle = shorten 80
, ppSep = "

Hi Felix, On 09/30/2010 01:29 PM, Felix Blanke wrote:
... I was using 2 screens with xmonad and xmobar.
The settings
ppCurrent = xmobarColor "#CC0000" "" . wrap "[" "]" , ppVisible = xmobarColor "#EE9A00" "" . wrap "[" "]" , ppTitle = shorten 80 , ppSep = "
|</fc>" , ppHiddenNoWindows = xmobarColor "#AFAF87" "" , ppUrgent = xmobarColor "#EE9A00" "" . wrap "[" "]" worked good for 2 screens: The active workspace is red and the inactive is orange.
But now, with 3 screens, there are 2 inactive workspaces and they both are orange. Is there a way to say:
inactive on screen 0 = blue inactive on screen 1 = ornage inactive on screen 3 = green
or something similar. ...
I'm not sure if the thing you want to achieve is (easily) possible with current implementation. But maybe you want to use better sorting algorithm, more suitable for configurations with more than 2 workspaces. This is how my PP looks like (the ppSort line is most interesting to you): ---8<--- myPP :: PP myPP = defaultPP { ppOutput = putStrLn , ppCurrent = color "yellow" "" , ppVisible = color "lightblue "" , ppUrgent = color "red" "" , ppSort = getSortByXineramaRule } where color = xmobarColor --->8--- Cheers, Juraj

Hi, thanks for that hint :) That does help, but for me it would be mutch nicer to have that thing with the different colors working. It is kind of confusing with that sorting thing: My primary monitor is the one in the middle. With that sorting thing the workspace visible at the middle monitor comes first, then the left one and then the right one. Would it be possible to change that? Like: Workspace on the left one is listed first, workspace on the middle one (primary) listed second and workspace on the right one listed third? It would be also nice to have a seperator after the first 3 workspaces :) Regards, Felix On 03. October 2010 - 14:44, Juraj Hercek wrote:
Date: Sun, 03 Oct 2010 14:44:06 +0200 From: Juraj Hercek
To: Felix Blanke CC: xmonad@haskell.org Subject: Re: [xmonad] ppVisible with 3 screens Hi Felix,
On 09/30/2010 01:29 PM, Felix Blanke wrote:
... I was using 2 screens with xmonad and xmobar.
The settings
ppCurrent = xmobarColor "#CC0000" "" . wrap "[" "]" , ppVisible = xmobarColor "#EE9A00" "" . wrap "[" "]" , ppTitle = shorten 80 , ppSep = "
|</fc>" , ppHiddenNoWindows = xmobarColor "#AFAF87" "" , ppUrgent = xmobarColor "#EE9A00" "" . wrap "[" "]" worked good for 2 screens: The active workspace is red and the inactive is orange.
But now, with 3 screens, there are 2 inactive workspaces and they both are orange. Is there a way to say:
inactive on screen 0 = blue inactive on screen 1 = ornage inactive on screen 3 = green
or something similar. ...
I'm not sure if the thing you want to achieve is (easily) possible with current implementation. But maybe you want to use better sorting algorithm, more suitable for configurations with more than 2 workspaces. This is how my PP looks like (the ppSort line is most interesting to you):
---8<--- myPP :: PP myPP = defaultPP { ppOutput = putStrLn , ppCurrent = color "yellow" "" , ppVisible = color "lightblue "" , ppUrgent = color "red" "" , ppSort = getSortByXineramaRule } where color = xmobarColor --->8---
Cheers, Juraj ---end quoted text---

Felix Blanke [2010.10.03 1618 +0200]:
Hi,
thanks for that hint :)
That does help, but for me it would be mutch nicer to have that thing with the different colors working.
It is kind of confusing with that sorting thing: My primary monitor is the one in the middle. With that sorting thing the workspace visible at the middle monitor comes first, then the left one and then the right one.
Would it be possible to change that? Like: Workspace on the left one is listed first, workspace on the middle one (primary) listed second and workspace on the right one listed third? It would be also nice to have a seperator after the first 3 workspaces :)
I have a setup like that working. I have two screens, and my status bar tells me what's on each screen, including their layouts, followed by a list of *all* workspaces, colour-coded according to whether or not they contain windows. So the end of my statusbar looks something like this: 1:Shell (Left) 3:Edit (Top) | 1234567890 with appropriate colours assigned to the 1234567890 sequence. The downside is that the only way I could see to achieve this is to collect this information myself from the stackset using hooks added to ppExtra. What you're trying to do can be done the same way. If you're willing to go to such lengths, I can elaborate. Come to think of it, what you are trying to do, including separator, can be done using just the right sorter, formatting function and a bit of postprocessing as follows: As sorter, you want to use X.U.WorkspaceCompare.getSortByXineramaRule. This places your visible workspaces first, sorted by screen. If that doesn't do what you want because the screens are not numbered left to right, you should look at the code of getSortByXineramaRule and tweak it to sort the visible workspaces the way you want. It's not hard. As formatting rule, you want (probably you want to add appropriate colouring): ppVisible = (++ "|") ppCurrent = (++ "|") ppHidden = id Finally, you want ppOrder = (\(ws:l:t:_) -> [postprocess ws, l, t]) with postprocess = delete '|' . delete '|' (For four screens, you would use three "delete '|'" here.) To get the "delete" function, you need to import Data.List. Cheers, Norbert
Regards, Felix
On 03. October 2010 - 14:44, Juraj Hercek wrote:
Date: Sun, 03 Oct 2010 14:44:06 +0200 From: Juraj Hercek
To: Felix Blanke CC: xmonad@haskell.org Subject: Re: [xmonad] ppVisible with 3 screens Hi Felix,
On 09/30/2010 01:29 PM, Felix Blanke wrote:
... I was using 2 screens with xmonad and xmobar.
The settings
ppCurrent = xmobarColor "#CC0000" "" . wrap "[" "]" , ppVisible = xmobarColor "#EE9A00" "" . wrap "[" "]" , ppTitle = shorten 80 , ppSep = "
|</fc>" , ppHiddenNoWindows = xmobarColor "#AFAF87" "" , ppUrgent = xmobarColor "#EE9A00" "" . wrap "[" "]" worked good for 2 screens: The active workspace is red and the inactive is orange.
But now, with 3 screens, there are 2 inactive workspaces and they both are orange. Is there a way to say:
inactive on screen 0 = blue inactive on screen 1 = ornage inactive on screen 3 = green
or something similar. ...
I'm not sure if the thing you want to achieve is (easily) possible with current implementation. But maybe you want to use better sorting algorithm, more suitable for configurations with more than 2 workspaces. This is how my PP looks like (the ppSort line is most interesting to you):
---8<--- myPP :: PP myPP = defaultPP { ppOutput = putStrLn , ppCurrent = color "yellow" "" , ppVisible = color "lightblue "" , ppUrgent = color "red" "" , ppSort = getSortByXineramaRule } where color = xmobarColor --->8---
Cheers, Juraj ---end quoted text---
xmonad mailing list xmonad@haskell.org http://www.haskell.org/mailman/listinfo/xmonad
-- () ascii ribbon campaign - against html e-mail /\ www.asciiribbon.org - against proprietary attachments

Hi Norbert, thanks a lot for your reply. There are some nice information in it. The last time I used haskell is a long time ago :) It will took me some time to understand what is going on in those functions. If you are some kind of haskel hacker and it takes you only one minute to change the function it would be great. Otherwise I'll post my result here if I did it. Those pp-variables works like they should! Thanks again for that great help. One last question about that: If I do it like you wrote the color of the "|"-seperator after the first three workspaces is the same as the color of ppVisible or ppCurrent ppVisible = xmobarColor "#EE9A00" "" . (++ " |") . wrap "[" "]" ppCurrent = xmobarColor "#CC0000" "" . (++ " |") . wrap "[" "]" Like I said: I'm a haskell noob. How can I set the color of the separator different? Regards, Felix On 03. October 2010 - 17:31, Norbert Zeh wrote:
Date: Sun, 3 Oct 2010 17:31:29 -0300 From: Norbert Zeh
To: xmonad@haskell.org Subject: Re: [xmonad] ppVisible with 3 screens Felix Blanke [2010.10.03 1618 +0200]:
Hi,
thanks for that hint :)
That does help, but for me it would be mutch nicer to have that thing with the different colors working.
It is kind of confusing with that sorting thing: My primary monitor is the one in the middle. With that sorting thing the workspace visible at the middle monitor comes first, then the left one and then the right one.
Would it be possible to change that? Like: Workspace on the left one is listed first, workspace on the middle one (primary) listed second and workspace on the right one listed third? It would be also nice to have a seperator after the first 3 workspaces :)
I have a setup like that working. I have two screens, and my status bar tells me what's on each screen, including their layouts, followed by a list of *all* workspaces, colour-coded according to whether or not they contain windows. So the end of my statusbar looks something like this:
1:Shell (Left) 3:Edit (Top) | 1234567890
with appropriate colours assigned to the 1234567890 sequence.
The downside is that the only way I could see to achieve this is to collect this information myself from the stackset using hooks added to ppExtra. What you're trying to do can be done the same way. If you're willing to go to such lengths, I can elaborate.
Come to think of it, what you are trying to do, including separator, can be done using just the right sorter, formatting function and a bit of postprocessing as follows:
As sorter, you want to use X.U.WorkspaceCompare.getSortByXineramaRule. This places your visible workspaces first, sorted by screen. If that doesn't do what you want because the screens are not numbered left to right, you should look at the code of getSortByXineramaRule and tweak it to sort the visible workspaces the way you want. It's not hard.
As formatting rule, you want (probably you want to add appropriate colouring):
ppVisible = (++ "|") ppCurrent = (++ "|") ppHidden = id
Finally, you want
ppOrder = (\(ws:l:t:_) -> [postprocess ws, l, t])
with
postprocess = delete '|' . delete '|' (For four screens, you would use three "delete '|'" here.)
To get the "delete" function, you need to import Data.List.
Cheers, Norbert
Regards, Felix
On 03. October 2010 - 14:44, Juraj Hercek wrote:
Date: Sun, 03 Oct 2010 14:44:06 +0200 From: Juraj Hercek
To: Felix Blanke CC: xmonad@haskell.org Subject: Re: [xmonad] ppVisible with 3 screens Hi Felix,
On 09/30/2010 01:29 PM, Felix Blanke wrote:
... I was using 2 screens with xmonad and xmobar.
The settings
ppCurrent = xmobarColor "#CC0000" "" . wrap "[" "]" , ppVisible = xmobarColor "#EE9A00" "" . wrap "[" "]" , ppTitle = shorten 80 , ppSep = "
|</fc>" , ppHiddenNoWindows = xmobarColor "#AFAF87" "" , ppUrgent = xmobarColor "#EE9A00" "" . wrap "[" "]" worked good for 2 screens: The active workspace is red and the inactive is orange.
But now, with 3 screens, there are 2 inactive workspaces and they both are orange. Is there a way to say:
inactive on screen 0 = blue inactive on screen 1 = ornage inactive on screen 3 = green
or something similar. ...
I'm not sure if the thing you want to achieve is (easily) possible with current implementation. But maybe you want to use better sorting algorithm, more suitable for configurations with more than 2 workspaces. This is how my PP looks like (the ppSort line is most interesting to you):
---8<--- myPP :: PP myPP = defaultPP { ppOutput = putStrLn , ppCurrent = color "yellow" "" , ppVisible = color "lightblue "" , ppUrgent = color "red" "" , ppSort = getSortByXineramaRule } where color = xmobarColor --->8---
Cheers, Juraj ---end quoted text---
xmonad mailing list xmonad@haskell.org http://www.haskell.org/mailman/listinfo/xmonad
--
() ascii ribbon campaign - against html e-mail /\ www.asciiribbon.org - against proprietary attachments _______________________________________________ xmonad mailing list xmonad@haskell.org http://www.haskell.org/mailman/listinfo/xmonad ---end quoted text---

Felix Blanke [2010.10.03 2305 +0200]:
Hi Norbert,
thanks a lot for your reply. There are some nice information in it.
The last time I used haskell is a long time ago :) It will took me some time to understand what is going on in those functions. If you are some kind of haskel hacker and it takes you only one minute to change the function it would be great. Otherwise I'll post my result here if I did it.
I'm not quite sure what you mean. Which function do you want to change?
Those pp-variables works like they should! Thanks again for that great help. One last question about that: If I do it like you wrote the color of the "|"-seperator after the first three workspaces is the same as the color of ppVisible or ppCurrent
ppVisible = xmobarColor "#EE9A00" "" . (++ " |") . wrap "[" "]" ppCurrent = xmobarColor "#CC0000" "" . (++ " |") . wrap "[" "]"
ppVisible = \s -> (xmobarColor "#EE9A00" "" $ wrap "[" "]" s) ++ (xmobarColor "whatever" "" " |") ppCurrent = dto. Cheers, Norbert

The getXineramaWsCompare maybe?! :) getXineramaWsCompare :: X WorkspaceCompare getXineramaWsCompare = do w <- gets windowset return $ \ a b -> case (isOnScreen a w, isOnScreen b w) of (True, True) -> comparing (tagToSid (onScreen w)) a b (False, False) -> compare a b (True, False) -> LT (False, True) -> GT where onScreen w = S.current w : S.visible w isOnScreen a w = a `elem` map (S.tag . S.workspace) (onScreen w) tagToSid s x = S.screen $ fromJust $ find ((== x) . S.tag . S.workspace) s The getSortByXineramaRule use that function: getSortByXineramaRule :: X WorkspaceSort getSortByXineramaRule = mkWsSort getXineramaWsCompare But like I said: I'm a haskell noob. When I understand those functions right the getXineramaWsCompare creates a ranking where the visible workspaces get the smallest id and mkWsSort then sorts that output. I have to thing about that how to change that ranking to get them in the right order. Regards, Felix On 03. October 2010 - 20:01, Norbert Zeh wrote:
Date: Sun, 3 Oct 2010 20:01:22 -0300 From: Norbert Zeh
To: Felix Blanke Cc: xmonad@haskell.org Subject: Re: [xmonad] ppVisible with 3 screens Felix Blanke [2010.10.03 2305 +0200]:
Hi Norbert,
thanks a lot for your reply. There are some nice information in it.
The last time I used haskell is a long time ago :) It will took me some time to understand what is going on in those functions. If you are some kind of haskel hacker and it takes you only one minute to change the function it would be great. Otherwise I'll post my result here if I did it.
I'm not quite sure what you mean. Which function do you want to change?
Those pp-variables works like they should! Thanks again for that great help. One last question about that: If I do it like you wrote the color of the "|"-seperator after the first three workspaces is the same as the color of ppVisible or ppCurrent
ppVisible = xmobarColor "#EE9A00" "" . (++ " |") . wrap "[" "]" ppCurrent = xmobarColor "#CC0000" "" . (++ " |") . wrap "[" "]"
ppVisible = \s -> (xmobarColor "#EE9A00" "" $ wrap "[" "]" s) ++ (xmobarColor "whatever" "" " |") ppCurrent = dto.
Cheers, Norbert ---end quoted text---

* On Monday, October 04 2010, Felix Blanke wrote:
But like I said: I'm a haskell noob. When I understand those functions right the getXineramaWsCompare creates a ranking where the visible workspaces get the smallest id and mkWsSort then sorts that output.
I have to thing about that how to change that ranking to get them in the right order.
Regards, Felix
Hello Felix, Perhaps you've missed in the same module: -- | -- 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. dynamicLogXinerama :: X () Or look at modifying pprWindowSetXinerama slightly in order to color those items differently. -- Adam

Hi Adam, the problem with your example is that my screen 1 is in the middle. That's why I want to see the workspace on screen 2 at the begin, then screen 1 and then screen 3. Norbert wants to have a look at those functions if he has some time. If I have the sorting in that way I wouldn't need that coloring anymore :) The sorting is a mutch nicer solution I think. Regards, Felix On 05. October 2010 - 01:59, Adam Vogt wrote:
Date: Tue, 5 Oct 2010 01:59:40 -0400 From: Adam Vogt
To: Felix Blanke Cc: xmonad@haskell.org Subject: Re: [xmonad] ppVisible with 3 screens * On Monday, October 04 2010, Felix Blanke wrote:
But like I said: I'm a haskell noob. When I understand those functions right the getXineramaWsCompare creates a ranking where the visible workspaces get the smallest id and mkWsSort then sorts that output.
I have to thing about that how to change that ranking to get them in the right order.
Regards, Felix
Hello Felix,
Perhaps you've missed in the same module:
-- | -- 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. dynamicLogXinerama :: X ()
Or look at modifying pprWindowSetXinerama slightly in order to color those items differently.
-- Adam ---end quoted text---

Felix Blanke [2010.10.04 0114 +0200]:
The getXineramaWsCompare maybe?! :)
getXineramaWsCompare :: X WorkspaceCompare getXineramaWsCompare = do w <- gets windowset return $ \ a b -> case (isOnScreen a w, isOnScreen b w) of (True, True) -> comparing (tagToSid (onScreen w)) a b (False, False) -> compare a b (True, False) -> LT (False, True) -> GT where onScreen w = S.current w : S.visible w isOnScreen a w = a `elem` map (S.tag . S.workspace) (onScreen w) tagToSid s x = S.screen $ fromJust $ find ((== x) . S.tag . S.workspace) s
The getSortByXineramaRule use that function:
getSortByXineramaRule :: X WorkspaceSort getSortByXineramaRule = mkWsSort getXineramaWsCompare
But like I said: I'm a haskell noob. When I understand those functions right the getXineramaWsCompare creates a ranking where the visible workspaces get the smallest id and mkWsSort then sorts that output.
I have to thing about that how to change that ranking to get them in the right order.
Alright, Felix, as promised here comes the way to do this. I'm not sure about your setup. So you may have to tweak it a little. I assume here that your left screen is #2, middle is #1, right is #3. The easiest way to get what you want (in addition to what I said in the previous email) is the following: 1) Hook your custom sorting function into the log hook ppSort = myXineramaSorter 2) Actually write your custom sorting function myXineramaSorter = do srt <- getSortByXineramaRule let prm (one:two:three:rest) = two:one:three:rest return (prm . srt) All this does is permute the first three workspaces (which the standard xinerama sorter guarantees are the visible ones) in the order (2,1,3). In this example, since we're only swapping the first two screens, you could actually simplify this to let prm (one:two:rest) = two:one:rest (Note: I'm typing this from a windows box :( and, thus, haven't tested this. Let me know if it doesn't work.) Now this does not do the colour coding you wanted, but that may actually no longer be necessary if you just see your three screens in the right order. Cheers, Norbert

Hello, thanks a lot for your work! It works :) The short version "let prm (one:two:rest) = two:one:rest" is enough, because I only need to switch the first two elements. With this hack I don't need the colour thing. Thanks again! Regards, Felix On 07. October 2010 - 21:31, Norbert Zeh wrote:
Date: Thu, 7 Oct 2010 21:31:44 -0300 From: Norbert Zeh
To: XMonad Mailing List Subject: Re: [xmonad] ppVisible with 3 screens Felix Blanke [2010.10.04 0114 +0200]:
The getXineramaWsCompare maybe?! :)
getXineramaWsCompare :: X WorkspaceCompare getXineramaWsCompare = do w <- gets windowset return $ \ a b -> case (isOnScreen a w, isOnScreen b w) of (True, True) -> comparing (tagToSid (onScreen w)) a b (False, False) -> compare a b (True, False) -> LT (False, True) -> GT where onScreen w = S.current w : S.visible w isOnScreen a w = a `elem` map (S.tag . S.workspace) (onScreen w) tagToSid s x = S.screen $ fromJust $ find ((== x) . S.tag . S.workspace) s
The getSortByXineramaRule use that function:
getSortByXineramaRule :: X WorkspaceSort getSortByXineramaRule = mkWsSort getXineramaWsCompare
But like I said: I'm a haskell noob. When I understand those functions right the getXineramaWsCompare creates a ranking where the visible workspaces get the smallest id and mkWsSort then sorts that output.
I have to thing about that how to change that ranking to get them in the right order.
Alright, Felix, as promised here comes the way to do this. I'm not sure about your setup. So you may have to tweak it a little. I assume here that your left screen is #2, middle is #1, right is #3.
The easiest way to get what you want (in addition to what I said in the previous email) is the following:
1) Hook your custom sorting function into the log hook
ppSort = myXineramaSorter
2) Actually write your custom sorting function
myXineramaSorter = do srt <- getSortByXineramaRule let prm (one:two:three:rest) = two:one:three:rest return (prm . srt)
All this does is permute the first three workspaces (which the standard xinerama sorter guarantees are the visible ones) in the order (2,1,3). In this example, since we're only swapping the first two screens, you could actually simplify this to
let prm (one:two:rest) = two:one:rest
(Note: I'm typing this from a windows box :( and, thus, haven't tested this. Let me know if it doesn't work.)
Now this does not do the colour coding you wanted, but that may actually no longer be necessary if you just see your three screens in the right order.
Cheers, Norbert _______________________________________________ xmonad mailing list xmonad@haskell.org http://www.haskell.org/mailman/listinfo/xmonad ---end quoted text---

* On Friday, October 08 2010, Felix Blanke wrote:
Hello,
thanks a lot for your work!
It works :) The short version
"let prm (one:two:rest) = two:one:rest"
is enough, because I only need to switch the first two elements. With this hack I don't need the colour thing.
Thanks again!
Regards, Felix
If you end up using that config with only one screen, that expression will throw an exception. XMonad will most likely catch it, but the recovery is to try again. Arguably xmonad should do something smarter, but until something changes there, you'd get an infinite loop. So add a fallback case to the definition: ] let prm (one:two:rest) = two:one:rest ] prm x = x -- Adam

Hi, are you sure that it doesn't work with only one screen? Even with only one screen "getSortByXineramaRule" returns a list with 9 workspaces (I'm using 9 workspaces) in it, right? Logicaly the sorting after the let is wrong then, but there should be no error. But like I said: I'm a haskell noob, maybe I'm totaly wrong :) How would I add that fallback? You wrote some ], but I'm not sure how such a fallback looks @haskell myXineramaSorter = do srt <- getSortByXineramaRule let prm (one:two:rest) = two:one:rest return (prm . srt) Felix On 09. October 2010 - 20:18, Adam Vogt wrote:
Date: Sat, 9 Oct 2010 20:18:58 -0400 From: Adam Vogt
To: xmonad@haskell.org Subject: Re: [xmonad] ppVisible with 3 screens * On Friday, October 08 2010, Felix Blanke wrote:
Hello,
thanks a lot for your work!
It works :) The short version
"let prm (one:two:rest) = two:one:rest"
is enough, because I only need to switch the first two elements. With this hack I don't need the colour thing.
Thanks again!
Regards, Felix
If you end up using that config with only one screen, that expression will throw an exception. XMonad will most likely catch it, but the recovery is to try again. Arguably xmonad should do something smarter, but until something changes there, you'd get an infinite loop.
So add a fallback case to the definition:
] let prm (one:two:rest) = two:one:rest ] prm x = x
-- Adam _______________________________________________ xmonad mailing list xmonad@haskell.org http://www.haskell.org/mailman/listinfo/xmonad ---end quoted text---

Felix Blanke [2010.10.10 1046 +0200]:
Hi,
are you sure that it doesn't work with only one screen?
Your are right here. This function will work on single screen, even though it won't do what you want (the first invisible screen would be the one listed first). However, Adam is right to the point that the pattern match of "prm" *can* fail under some circumstances, namely when you run this with less than two workspaces. This, however, would be a change in your xmonad.hs, and that means you should inspect everything else in your setup for correctness anyway. Cheers, Norbert
Even with only one screen "getSortByXineramaRule" returns a list with 9 workspaces (I'm using 9 workspaces) in it, right? Logicaly the sorting after the let is wrong then, but there should be no error.
But like I said: I'm a haskell noob, maybe I'm totaly wrong :)
How would I add that fallback? You wrote some ], but I'm not sure how such a fallback looks @haskell
myXineramaSorter = do srt <- getSortByXineramaRule let prm (one:two:rest) = two:one:rest return (prm . srt)
Felix
On 09. October 2010 - 20:18, Adam Vogt wrote:
Date: Sat, 9 Oct 2010 20:18:58 -0400 From: Adam Vogt
To: xmonad@haskell.org Subject: Re: [xmonad] ppVisible with 3 screens * On Friday, October 08 2010, Felix Blanke wrote:
Hello,
thanks a lot for your work!
It works :) The short version
"let prm (one:two:rest) = two:one:rest"
is enough, because I only need to switch the first two elements. With this hack I don't need the colour thing.
Thanks again!
Regards, Felix
If you end up using that config with only one screen, that expression will throw an exception. XMonad will most likely catch it, but the recovery is to try again. Arguably xmonad should do something smarter, but until something changes there, you'd get an infinite loop.
So add a fallback case to the definition:
] let prm (one:two:rest) = two:one:rest ] prm x = x
-- Adam _______________________________________________ xmonad mailing list xmonad@haskell.org http://www.haskell.org/mailman/listinfo/xmonad ---end quoted text---
xmonad mailing list xmonad@haskell.org http://www.haskell.org/mailman/listinfo/xmonad
-- () ascii ribbon campaign - against html e-mail /\ www.asciiribbon.org - against proprietary attachments

* On Sunday, October 10 2010, Felix Blanke wrote:
Hi,
are you sure that it doesn't work with only one screen?
Even with only one screen "getSortByXineramaRule" returns a list with 9 workspaces (I'm using 9 workspaces) in it, right? Logicaly the sorting after the let is wrong then, but there should be no error.
But like I said: I'm a haskell noob, maybe I'm totaly wrong :)
How would I add that fallback? You wrote some ], but I'm not sure how such a fallback looks @haskell
myXineramaSorter = do srt <- getSortByXineramaRule let prm (one:two:rest) = two:one:rest return (prm . srt)
Felix
You're right, the list of workspaces is being sorted. So my point about number of screens should be about the number of workspaces, and nobody ever has a single workspace. So the problem is purely academic. But here is how the whole thing looks: myXineramaSorter = do srt <- getSortByXineramaRule let prm (one:two:rest) = two:one:rest prm x = x return (prm . srt) -- Adam
participants (4)
-
Adam Vogt
-
Felix Blanke
-
Juraj Hercek
-
Norbert Zeh