
#8227: cgLookupPanic (probably invalid Core ---------------------------------------+----------------------------------- Reporter: guest | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 7.6.3 Resolution: fixed | Keywords: cgLookupPanic Operating System: MacOS X | Architecture: Type of failure: Compile-time crash | Unknown/Multiple Test Case: | Difficulty: Unknown Blocking: | Blocked By: | Related Tickets: ---------------------------------------+----------------------------------- Changes (by monoidal): * status: new => closed * resolution: => fixed Comment: I distilled the part that causes panic in 7.6.3 and that part gives a correct type error in HEAD. The crucial part is this: {{{ arcLengthToParam :: Scalar (V p) -> p -> Scalar (V p) -> Scalar (V p) absoluteToParam :: Scalar (V a) -> a -> Scalar (V a) -> Scalar (V a) absoluteToParam eps seg len = arcLengthToParam eps (arcLength eps seg - len) -- You probably wanted absoluteToParam eps seg len = arcLengthToParam eps seg (arcLength eps seg - len) }}} By skipping this parameter GHC has to solve `Scalar (V a) ~ a` and `Scalar (V a) -> Scalar (V p) ~ Scalar (V p)` and gets a headache. Here's a selfcontained test that panicks 7.6.3 gives occurs check in HEAD: {{{ {-# LANGUAGE TypeFamilies #-} module V where type family V a :: * type instance V Double = Double type instance V (a -> b) = V b {-# LANGUAGE TypeFamilies #-} module Parametric ( absoluteToParam ) where import V type family Scalar a :: * type instance Scalar (a -> v) = a -> Scalar v arcLengthToParam :: Scalar (V p) -> p -> Scalar (V p) -> Scalar (V p) arcLengthToParam = undefined absoluteToParam :: Scalar (V a) -> a -> Scalar (V a) absoluteToParam eps seg = arcLengthToParam eps eps }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8227#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler