[xmonad] Can I switch layouts based on number of windows in a workspace?

Jeffrey David Johnson jefdaj at gmail.com
Tue Aug 28 07:46:54 CEST 2012


OK that makes sense I think. I ran into another problem though when 
trying to integrate it into my xmonad.hs. I used:

myLayoutHook = onlyFor Multiple (spacing 2) $ Tall 1 (3/100) (1/2)

and got this big long error. Something about Read instances, but all the 
data declarations in OnlyFor.hs have

deriving (Read, Show)

on them so I'm not sure what's up with that.
Jeff

jefdaj at acro:~/.xmonad$ ghc --make OnlyFor.hs xmonad.hs -o 
xmonad-x86_64-linux
[2 of 2] Compiling Main             ( xmonad.hs, xmonad.o )

xmonad.hs:199:5:
     No instances for (Read
                         (l0 a0
                          -> XMonad.Layout.LayoutModifier.ModifiedLayout 
Spacing l0 a0),
                       XMonad.Layout.LayoutModifier.LayoutModifier
                         (OnlyFor
                            (l0 a0
                             -> 
XMonad.Layout.LayoutModifier.ModifiedLayout Spacing l0 a0))
                         GHC.Word.Word64)
       arising from a use of `xmonad'
     Possible fix:
       add instance declarations for
       (Read
          (l0 a0
           -> XMonad.Layout.LayoutModifier.ModifiedLayout Spacing l0 a0),
        XMonad.Layout.LayoutModifier.LayoutModifier
          (OnlyFor
             (l0 a0
              -> XMonad.Layout.LayoutModifier.ModifiedLayout Spacing l0 a0))
          GHC.Word.Word64)
     In the expression: xmonad
     In a stmt of a 'do' block:
       xmonad
       $ defaultConfig
           {terminal = "lxterminal", borderWidth = 2, modMask = mod4Mask,
            keys = myKeys, workspaces = myWorkspaces,
            handleEventHook = myHandleEventHook, layoutHook = myLayoutHook,
            manageHook = myManageHook, logHook = myLogHook toolbarPipe,
            normalBorderColor = myNormalBorderColor,
            focusedBorderColor = myFocusedBorderColor}
     In the expression:
       do { spawn myBackgroundApps;
            toolbarPipe <- spawnPipe myToolbar;
            xmonad
            $ defaultConfig
                {terminal = "lxterminal", borderWidth = 2, modMask = 
mod4Mask,
                 keys = myKeys, workspaces = myWorkspaces,
                 handleEventHook = myHandleEventHook, layoutHook = 
myLayoutHook,
                 manageHook = myManageHook, logHook = myLogHook toolbarPipe,
                 normalBorderColor = myNormalBorderColor,
                 focusedBorderColor = myFocusedBorderColor} }



On 08/27/2012 11:01 AM, Brandon Allbery wrote:
> On Mon, Aug 27, 2012 at 1:36 PM, Jeffrey David Johnson 
> <jefdaj at gmail.com <mailto:jefdaj at gmail.com>> wrote:
>
>     Thanks, I'll read through this and try to figure it out when I get
>     a chance (maybe later today). In the meantime I get a compile error:
>
>     jefdaj at acro:~/.xmonad$ <mailto:jefdaj at acro:%7E/.xmonad$> ghc
>     --make OnlyFor.hs
>     [1 of 1] Compiling XMonad.Layout.OnlyFor ( OnlyFor.hs, OnlyFor.o )
>     OnlyFor.hs:60:64:
>         `m' is applied to too many type arguments
>
>
> *sigh* sorry, thought that was already fixed in that copy of the 
> source.  (this is why I retracted original patches and am not 
> releasing until I can get my working environment back going....)  ghci 
> should be correct.
>
>     onlyFor
>       :: HowMany
>          -> m
>          -> l a
>          -> XMonad.Layout.LayoutModifier.ModifiedLayout (OnlyFor m) l a
>
>     Does that look reasonable? m is One | Multiple, l is the
>     LayoutModifier and a is the Layout right?
>
>
> "m" is the layout modifier to be applied, "l a" is the layout modifier 
> to apply it to, "a" is instantiated to Window in xmonad and to a dummy 
> when running pure tests.
>
> -- 
> brandon s allbery allbery.b at gmail.com <mailto:allbery.b at gmail.com>
> wandering unix systems administrator (available)     (412) 475-9364 vm/sms
>

-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/xmonad/attachments/20120827/0d3feb69/attachment-0001.htm>


More information about the xmonad mailing list