[GHC] #13754: ghc-8.0.2+ rejects more instance declarations
GHC
ghc-devs at haskell.org
Thu May 25 13:55:57 UTC 2017
#13754: ghc-8.0.2+ rejects more instance declarations
-------------------------------------+-------------------------------------
Reporter: zilinc | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 8.0.2
Keywords: | Operating System: Unknown/Multiple
Architecture: | Type of failure: None/Unknown
Unknown/Multiple |
Test Case: | Blocked By:
Blocking: | Related Tickets:
Differential Rev(s): | Wiki Page:
-------------------------------------+-------------------------------------
Sorry for the vague title.
For a program (sorry again but I failed to shrink it further):
{{{
{-# language ExistentialQuantification, KindSignatures, DataKinds, GADTs,
UndecidableInstances, AllowAmbiguousTypes #-}
class Pretty a where
pretty :: a -> String
prettyList :: [a] -> String
prettyList = concatMap pretty
data Def e = forall t. FunDef (Type t) (e t)
data Nat = Z | S Nat
data F (t :: Nat) where
FZ :: F (S Z)
FS :: F n -> F (S n)
data Type (t :: Nat) = TVar (F t)
data Expr (t :: Nat) e = Fun (Type t)
| App (e t) (e t)
data TE t = TE (Type t) (Expr t TE)
-- all methods left undefined, as they're insignificant
instance Pretty t => Pretty [t] where
pretty = undefined
instance (Pretty (e t)) => Pretty (Def e) where
pretty (FunDef t e) = undefined
instance Pretty (Type t) where
pretty (TVar t) = undefined
instance Pretty (e t) => Pretty (Expr t e) where
pretty (Fun t) = undefined
pretty (App e1 e2) = undefined
instance Pretty (TE t) where
pretty (TE t e) = undefined
}}}
ghc-8.0.1 is happy with it, whereas later versions (tested with 8.0.2 and
8.2.1-rc2) reject it. The error msg is:
{{{
GHCInstance1.hs:27:10: error:
• Could not deduce (Pretty (e t0))
arising from a use of ‘Main.$dmprettyList’
from the context: Pretty (e t)
bound by the instance declaration at GHCInstance1.hs:27:10-41
The type variable ‘t0’ is ambiguous
Relevant bindings include
prettyList :: [Def e] -> String (bound at GHCInstance1.hs:27:10)
• In the expression: Main.$dmprettyList @Def e
In an equation for ‘prettyList’:
prettyList = Main.$dmprettyList @Def e
In the instance declaration for ‘Pretty (Def e)’
}}}
If I comment out the `prettyList` method from the class definition, then
all happy. I'm not sure if it's a bug in 8.0.1 or a regression (and hard
to reason about the behaviours). If it was the later, how should I migrate
from 8.0.1? The `Pretty` class is a library (e.g. ansi-wl-pprint) so no
way I can change it.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/13754>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list