[GHC] #11754: Error in optCoercion
GHC
ghc-devs at haskell.org
Fri Mar 25 09:38:13 UTC 2016
#11754: Error in optCoercion
-------------------------------------+-------------------------------------
Reporter: simonpj | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 7.10.3
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:
-------------------------------------+-------------------------------------
This program fails Lint after a run of the simplifier.
{{{
{-# LANGUAGE TypeOperators, UndecidableSuperClasses, KindSignatures,
TypeFamilies, FlexibleContexts #-}
module T11728a where
import Data.Kind
import Data.Void
newtype K a x = K a
newtype I x = I x
data (f + g) x = L (f x) | R (g x)
data (f × g) x = f x :×: g x
class Differentiable (D f) => Differentiable f where
type D (f :: Type -> Type) :: Type -> Type
instance Differentiable (K a) where
type D (K a) = K Void
instance Differentiable I where
type D I = K ()
instance (Differentiable f₁, Differentiable f₂) => Differentiable (f₁ +
f₂) where
type D (f₁ + f₂) = D f₁ + D f₂
instance (Differentiable f₁, Differentiable f₂) => Differentiable (f₁ ×
f₂) where
type D (f₁ × f₂) = (D f₁ × f₂) + (f₁ × D f₂)
}}}
Originally reported in #11728, but it's a totally different problem.
Richard has nailed it already... patch coming from him.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/11754>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list