GHC 7.0.1 rc1: Could not deduce (Typeable a) from the context (Typeable a, …)
Malte Sommerkorn
malte.sommerkorn at googlemail.com
Wed Sep 29 14:50:24 EDT 2010
While compile failures were easy to fix for syb, X11 and xmonad, here's a more
mysterious encounter with xmonad-contrib. The module in question is
http://code.haskell.org/XMonadContrib/XMonad/Layout/MultiToggle.hs
and the rest of this mail is the error:
XMonad/Layout/MultiToggle.hs:194:30:
Could not deduce (Typeable a)
from the context (Typeable a, Show ts, HList ts a, LayoutClass l a)
arising from a use of `fromMessage'
Possible fix:
add (Typeable a) to the context of the instance declaration
In a stmt of a pattern guard for
an equation for `handleMessage':
Just (Toggle t) <- fromMessage m
In an equation for `handleMessage':
handleMessage mt m
| Just (Toggle t) <- fromMessage m,
i@(Just _) <- find (transformers mt) t
= case currLayout mt of {
EL l det
-> do { l' <- fromMaybe l
`fmap`
handleMessage l (SomeMessage ReleaseResources);
.... }
where
cur = (i == currIndex mt) }
| otherwise
= case currLayout mt of {
EL l det
-> fmap (fmap (\ x -> mt {currLayout = EL x det}))
$ handleMessage l m }
In the instance declaration for `LayoutClass (MultiToggle ts l) a'
XMonad/Layout/MultiToggle.hs:195:25:
Could not deduce (HList ts a)
from the context (Typeable a,
Show ts,
HList ts a,
LayoutClass l a,
Transformer t a)
arising from a use of `find'
Possible fix:
add (HList ts a) to the context of
the data constructor `Toggle'
or the instance declaration
In a stmt of a pattern guard for
an equation for `handleMessage':
i@(Just _) <- find (transformers mt) t
In a stmt of a pattern guard for
an equation for `handleMessage':
Just (Toggle t) <- fromMessage m
In an equation for `handleMessage':
handleMessage mt m
| Just (Toggle t) <- fromMessage m,
i@(Just _) <- find (transformers mt) t
= case currLayout mt of {
EL l det
-> do { l' <- fromMaybe l
`fmap`
handleMessage l (SomeMessage ReleaseResources);
.... }
where
cur = (i == currIndex mt) }
| otherwise
= case currLayout mt of {
EL l det
-> fmap (fmap (\ x -> mt {currLayout = EL x det}))
$ handleMessage l m }
More information about the Glasgow-haskell-users
mailing list