[xmonad] Full example of IndependentScreens

Ola Karlsson skalle.karlsson at gmail.com
Fri Apr 8 04:27:30 CEST 2011


Hi all..

Changed my code as ~d suggested but still get the err msg:

xmonad.hs:8:51:
    Couldn't match expected type `M.Map k a'

Getting a bit personal now so'll dig into some haskell documentation to fix
this myself after work..
When/If i end up with a working config or a computer thrown out from 6th
floor I'll post back here..

/Ola




On Fri, Apr 8, 2011 at 12:02 PM, <wagnerdm at seas.upenn.edu> wrote:

> Gotta lose that dollar sign at the end of the line beginning "myKeys". =)
> Also, make sure to change workspaces to workspaces' (notice the single
> quote at the end), and change "windows $ f i" to "windows $ onCurrentScreen
> f i", as detailed in the documentation.
>
> ~d
>
> Quoting Ola Karlsson <skalle.karlsson at gmail.com>:
>
>  Hi ~d and rest of you haskell wizards..
>>
>> Long time since i felt this green at something.. :)
>> Did your changes and ended up with this.
>>
>> import XMonad
>> import XMonad.Config.Gnome
>> import qualified Data.Map as M
>> import qualified XMonad.StackSet as W
>> import XMonad.Layout.IndependentScreens
>>
>> -- myKeys conf@(XConfig {XMonad.modMask = modMask}) = M.fromList $
>> myKeys conf@(XConfig {XMonad.modMask = modMask}) = keys defaultConfig
>> `M.union` M.fromList $
>>
>> --      ++
>>        [ ((m .|. modMask, k ), windows $ f i)
>>                | (i, k) <- zip (workspaces conf) [xK_1 .. xK_9]
>>                , (f,m) <- [(W.greedyView, 0), (W.shift, shiftMask)]]
>>
>>
>> main = xmonad gnomeConfig
>>        { terminal = "urxvt -rv +sb"
>>        , modMask = mod4Mask
>>        , workspaces = withScreens 2 ["Monitor" , "Work"]
>>        , keys = myKeys
>>        }
>>
>> Still some hate from the compiler though:
>>
>> xmonad.hs:8:51:
>>    Couldn't match expected type `M.Map k a'
>>           against inferred type `XConfig Layout
>>                                  -> M.Map (ButtonMask, KeySym) (X ())'
>>    In the first argument of `M.union', namely `keys defaultConfig'
>>    In the first argument of `($)', namely
>>        `keys defaultConfig `M.union` M.fromList'
>>    In the expression:
>>            keys defaultConfig `M.union` M.fromList
>>        $ [((m .|. modMask, k), windows $ f i) |
>>               (i, k) <- zip (workspaces conf) [xK_1 .. xK_9],
>>               (f, m) <- [(W.greedyView, 0), (W.shift, shiftMask)]]
>>
>> Tried without the keys defaultConfig and the thing compiled fine but as
>> expected lost all my keys except the ch. workspace ones that still worked
>> like default.. :(
>>
>> So a little bit stuck again ..
>>
>> /Ola
>>
>> On Thu, Apr 7, 2011 at 10:30 PM, <wagnerdm at seas.upenn.edu> wrote:
>>
>>  Great! Now that there's some code to critique, I can help a bit. =)
>>>
>>> To fix the scoping errors:
>>>
>>> import qualified Data.Map as M
>>> import qualified XMonad.StackSet as W
>>>
>>> You'll also want to make these changes:
>>>
>>> On the line defining myKeys, make sure you keep the keys from the default
>>> configuration:
>>>
>>> myKeys conf@(...as before...) = keys defaultConfig `M.union` M.fromList
>>>   [ ...as before... ]
>>>
>>> Also, as mentioned in the documentation, you'll want to use workspaces'
>>> instead of XMonad.workspaces when defining your keybindings, so change
>>> that
>>> line to:
>>>       | (i, k) <- zip (workspaces' conf) [xK_1 .. xK_9]
>>>
>>> Additionally, I expect that IndependentScreens is mostly useless if you
>>> have only one screen. I don't know how many screens you do have, but
>>> assuming it's two, the line inside of main should look like this:
>>>
>>>       , workspaces = withScreens 2 ["Monitor", "Work"]
>>>
>>> If you have three screens, change the 2 to 3, etc. Finally, you have to
>>> make sure to inform xmonad of your custom bindings in myKeys, so add a
>>> line
>>> right after that like this:
>>>
>>>       , keys = myKeys
>>>
>>> Good luck! Let us know how it goes after these changes.
>>> ~d
>>>
>>>
>>> Quoting Ola Karlsson <skalle.karlsson at gmail.com>:
>>>
>>>  Hi Linux..
>>>
>>>>
>>>> Thx for answering my newbie questions.. Haskell is something brand new
>>>> and
>>>> strange to me so am just hacking around at random in the config.hs with
>>>> little luck..
>>>>
>>>> Did read the usage part and ended up with this config...
>>>>
>>>> import XMonad
>>>> import XMonad.Config.Gnome
>>>> import XMonad.Layout.IndependentScreens
>>>> myKeys conf@(XConfig {XMonad.modMask = modMask}) = M.fromList $
>>>>
>>>> --      ++
>>>>     [ ((m .|. modMask, k ), windows $ f i)
>>>>             | (i, k) <- zip (XMonad.workspaces conf) [xK_1 .. xK_9]
>>>>             , (f,m) <- [(W.greedyView, 0), (W.shift, shiftMask)]]
>>>>
>>>>
>>>> main = xmonad gnomeConfig
>>>>       { terminal = "urxvt -rv +sb"
>>>>       , modMask = mod4Mask
>>>>       , workspaces = withScreens 1 ["Monitor" , "Work"]
>>>>       }
>>>>
>>>> With this I end up with
>>>>
>>>> xmonad.hs:5:51: Not in scope: `M.fromList'
>>>>
>>>> xmonad.hs:10:15: Not in scope: `W.greedyView'
>>>>
>>>> xmonad.hs:10:34: Not in scope: `W.shift'
>>>>
>>>> And am stuck.. :(
>>>>
>>>> /Ola
>>>>
>>>>
>>>> On Thu, Apr 7, 2011 at 3:09 PM, Linus Arver <linusarver at gmail.com>
>>>> wrote:
>>>>
>>>>  >    Have one problem though , Multiple Screens , can't wrap my head
>>>>
>>>>> around
>>>>> how
>>>>> >    xmonad handles that default and want to go for the way I'm used to
>>>>> have it
>>>>> >    work with separate workspaces for each screen..
>>>>>
>>>>> In Xmonad, there are N workspaces (you can define as many as you like).
>>>>> Most people have 9 of them, because that's the default config. I
>>>>> personally have 22 workspaces (hotkeyed to modm + 1-9, F1-F12). Each
>>>>> workspace can have N windows in it. Anyway, each screen (monitor) can
>>>>> view any 1 workspace at a time. That's all there's to it...
>>>>>
>>>>> >    Found the IndependentScreens thing in the documentation but can't
>>>>> figure
>>>>> >    out how to get it in the configuration so needs some help..
>>>>>
>>>>> The "Usage" section at
>>>>>
>>>>>
>>>>>
>>>>> http://xmonad.org/xmonad-docs/xmonad-contrib/XMonad-Layout-IndependentScreens.html
>>>>> seems to have everything you're looking for. After editing your
>>>>> xmonad.hs, just run "ghci" on it: ghci xmonad.hs. If you get any
>>>>> errors,
>>>>> then your config is messed up.
>>>>>
>>>>> >    Could someone give me a working example of a Gnome enables xmonad
>>>>> config
>>>>> >    that uses IndependentScreens?
>>>>>
>>>>> A quick google search got me this:
>>>>> http://www.haskell.org/pipermail/xmonad/2009-December/009466.html
>>>>> Maybe you should ask the user there about it...
>>>>>
>>>>> Personally though, I'd just stick with the default. There are lots of
>>>>> neat contrib modules out there (e.g., CycleWS) that rely on the default
>>>>> setup (1 set of workspaces). You'd have to hack all of those modules to
>>>>> get them working with your IndependentScreens setup.
>>>>>
>>>>> -Linus
>>>>>
>>>>>
>>>>>
>>>>
>>>
>>> _______________________________________________
>>> xmonad mailing list
>>> xmonad at haskell.org
>>> http://www.haskell.org/mailman/listinfo/xmonad
>>>
>>>
>>
>
>
> _______________________________________________
> xmonad mailing list
> xmonad at haskell.org
> http://www.haskell.org/mailman/listinfo/xmonad
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/xmonad/attachments/20110408/9cb0e98b/attachment-0001.htm>


More information about the xmonad mailing list