GHC 7.0.1 rc1: Could not deduce (Typeable a) from the context (Typeable a, …)

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 }

Oh dear, that really is quite a strange error message. Something is definitely wrong. Can you please make a ticket for it, and include instructions on how to reproduce it? I gather that it depends on other packages that themselves needed changes, so reproduction might not be entirely easy? Simon | -----Original Message----- | From: glasgow-haskell-users-bounces@haskell.org [mailto:glasgow-haskell-users- | bounces@haskell.org] On Behalf Of Malte Sommerkorn | Sent: 29 September 2010 19:50 | To: glasgow-haskell-users@haskell.org | Subject: GHC 7.0.1 rc1: Could not deduce (Typeable a) from the context (Typeable a, | …) | | 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 } | | _______________________________________________ | Glasgow-haskell-users mailing list | Glasgow-haskell-users@haskell.org | http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

Simon Peyton-Jones wrote:
Oh dear, that really is quite a strange error message. Something is definitely wrong. Can you please make a ticket for it, and include instructions on how to reproduce it?
Done: http://hackage.haskell.org/trac/ghc/ticket/4355
I gather that it depends on other packages that themselves needed changes, so reproduction might not be entirely easy?
I've attached a module to the bug report that triggers the problem and only depends on base and mtl, so that should be fairly easy to reproduce. Regards Malte

Thank you! I can reproduce it. It is a truly egregious error. It will be fixed. Simon | -----Original Message----- | From: glasgow-haskell-users-bounces@haskell.org [mailto:glasgow-haskell-users- | bounces@haskell.org] On Behalf Of Malte Sommerkorn | Sent: 30 September 2010 15:55 | To: Simon Peyton-Jones | Cc: glasgow-haskell-users@haskell.org | Subject: Re: GHC 7.0.1 rc1: Could not deduce (Typeable a) from the context (Typeable | a, …) | | Simon Peyton-Jones wrote: | > Oh dear, that really is quite a strange error message. Something is | > definitely wrong. Can you please make a ticket for it, and include | > instructions on how to reproduce it? | | Done: http://hackage.haskell.org/trac/ghc/ticket/4355 | | > I gather that it depends on other packages that themselves needed changes, | > so reproduction might not be entirely easy? | | I've attached a module to the bug report that triggers the problem and only | depends on base and mtl, so that should be fairly easy to reproduce. | | Regards | Malte | | _______________________________________________ | Glasgow-haskell-users mailing list | Glasgow-haskell-users@haskell.org | http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
participants (2)
-
Malte Sommerkorn
-
Simon Peyton-Jones