[xmonad] MultiToggle + Decorations breaks upgrading to 0.10

Joseph Garvin joseph.h.garvin at gmail.com
Sat Sep 22 17:18:15 CEST 2012


I just upgraded from 0.9 to 0.10 and had to comment out the following
to get my xmonad.hs to compile:

data DECORATIONS = DECORATIONS deriving (Read, Show, Eq, Typeable)
instance MultiToggle.Transformer DECORATIONS Window where
		 transform _ x k = k (simpleDeco shrinkText (defaultTheme {
decoWidth = 9999999, fontName =
"-*-helvetica-bold-r-*-*-14-*-*-*-*-*-*-*", inactiveColor = "black",
activeColor = "black", activeTextColor = "red", inactiveTextColor =
"green" } ) x)

Which gives me this glorious error:

xmonad.hs:10:16:
    Warning: -fglasgow-exts is deprecated: Use individual extensions instead

xmonad.hs:247:36:
    Couldn't match type `b'
                   with `(XMonad.Layout.LayoutModifier.ModifiedLayout
                            (XMonad.Layout.Decoration.Decoration
                               SimpleDecoration
XMonad.Layout.Decoration.DefaultShrinker)
                            l
                            GHC.Word.Word64
                          -> l GHC.Word.Word64)
                         -> b'
      `b' is a rigid type variable bound by
          the type signature for
            transform :: LayoutClass l Window =>
                         DECORATIONS
                         -> l Window
                         -> (forall (l' :: * -> *).
                             LayoutClass l' Window =>
                             l' Window -> (l' Window -> l Window) -> b)
                         -> b
          at xmonad.hs:247:18
    In the return type of a call of `k'
    Probable cause: `k' is applied to too few arguments
    In the expression:
      k (simpleDeco
           shrinkText
           (defaultTheme
              {decoWidth = 9999999,
               fontName = "-*-helvetica-bold-r-*-*-14-*-*-*-*-*-*-*",
               inactiveColor = "black", activeColor = "black",
               activeTextColor = "red", inactiveTextColor = "green"})
           x)
    In an equation for `transform':
        transform _ x k
          = k (simpleDeco
                 shrinkText
                 (defaultTheme
                    {decoWidth = 9999999,
                     fontName = "-*-helvetica-bold-r-*-*-14-*-*-*-*-*-*-*",
                     inactiveColor = "black", activeColor = "black",
                     activeTextColor = "red", inactiveTextColor = "green"})
                 x)

I see that it's complaining that k is applied to too few arguments, so
I looked in the docs for MultiToggle and in their example it looks
like k takes what looks like a lambda (I'm actually confused by the
syntax, I've never seen parens around a lambda parameter) as a second
argument now for some reason:

 data MIRROR = MIRROR deriving (Read, Show, Eq, Typeable)
 instance Transformer MIRROR Window where
     transform _ x k = k (Mirror x) (\(Mirror x') -> x')

But I'm too much of a Haskell newb to adapt my decoration snippet for
that. Help?

Thanks,

Joe G.



More information about the xmonad mailing list