[GHC] #7862: Could not deduce (A) from the context (A, ...)
GHC
cvs-ghc at haskell.org
Thu Apr 25 09:56:55 CEST 2013
#7862: Could not deduce (A) from the context (A, ...)
--------------------------------------+-------------------------------------
Reporter: alang9 | Owner:
Type: bug | Status: new
Priority: normal | Component: Compiler (Type checker)
Version: 7.6.2 | Keywords:
Os: Linux | Architecture: x86_64 (amd64)
Failure: GHC rejects valid program | Blockedby:
Blocking: | Related:
--------------------------------------+-------------------------------------
The following code doesn't compile and produces a strange error:
{{{
{-# LANGUAGE TypeFamilies, FlexibleContexts #-}
module Numeric.AD.Internal.Tower () where
type family Scalar t
newtype Tower s a = Tower [a]
type instance Scalar (Tower s a) = a
class (Num (Scalar t), Num t) => Mode t where
(<+>) :: t -> t -> t
instance (Num a) => Mode (Tower s a) where
Tower as <+> _ = undefined
where
_ = (Tower as) <+> (Tower as)
instance Num a => Num (Tower s a) where
}}}
{{{
src/Numeric/AD/Internal/Tower.hs:17:24:
Could not deduce (Num (Scalar (Tower s a)))
arising from a use of `<+>'
from the context (Num (Scalar (Tower s a)), Num (Tower s a), Num a)
bound by the instance declaration
at src/Numeric/AD/Internal/Tower.hs:14:10-36
Possible fix:
add an instance declaration for (Num (Scalar (Tower s a)))
In the expression: (Tower as) <+> (Tower as)
In a pattern binding: _ = (Tower as) <+> (Tower as)
In an equation for `<+>':
(Tower as) <+> _
= undefined
where
_ = (Tower as) <+> (Tower as)
}}}
Furthermore, Removing the {{{Num (Scalar t)}}} constraint from the
{{{Mode}}} class produces a different strange error:
{{{
src/Numeric/AD/Internal/Tower.hs:17:24:
Overlapping instances for Num (Tower s0 a)
arising from a use of `<+>'
Matching givens (or their superclasses):
(Num (Tower s a))
bound by the instance declaration
at src/Numeric/AD/Internal/Tower.hs:14:10-36
Matching instances:
instance Num a => Num (Tower s a)
-- Defined at src/Numeric/AD/Internal/Tower.hs:19:10
(The choice depends on the instantiation of `a, s0')
In the expression: (Tower as) <+> (Tower as)
In a pattern binding: _ = (Tower as) <+> (Tower as)
In an equation for `<+>':
(Tower as) <+> _
= undefined
where
_ = (Tower as) <+> (Tower as)
}}}
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/7862>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list