
#12944: ghc master (8.1.20161206) panics with assertion failure with devel2 flavor and -O -------------------------------------+------------------------------------- Reporter: pacak | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.1 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: Compile-time Unknown/Multiple | crash or panic Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- ghc version: 41ec722d71 with assertion that fails in https://ghc.haskell.org/trac/ghc/ticket/12926 commented out {{{#!hs {-# LANGUAGE TypeFamilies #-} module Numeric.Polynomial.Log () where class AdditiveGroup v where (^+^) :: v -> v -> v negateV :: v -> v (^-^) :: v -> v -> v v ^-^ v' = v ^+^ negateV v' class AdditiveGroup v => VectorSpace v where type Scalar v :: * (*^) :: Scalar v -> v -> v data Poly1 a = Poly1 a a data IntOfLog poly a = IntOfLog !a !(poly a) instance Num a => AdditiveGroup (Poly1 a) where {-# INLINE (^+^) #-} {-# INLINE negateV #-} Poly1 a b ^+^ Poly1 a' b' = Poly1 (a + a') (b + b') negateV (Poly1 a b) = Poly1 (negate a) (negate b) instance (AdditiveGroup (poly a), Num a) => AdditiveGroup (IntOfLog poly a) where {-# INLINE (^+^) #-} {-# INLINE negateV #-} IntOfLog k p ^+^ IntOfLog k' p' = IntOfLog (k + k') (p ^+^ p') negateV (IntOfLog k p) = IntOfLog (negate k) (negateV p) {-# SPECIALISE instance Num a => AdditiveGroup (IntOfLog Poly1 a) #-} instance (VectorSpace (poly a), Scalar (poly a) ~ a, Num a) => VectorSpace (IntOfLog poly a) where type Scalar (IntOfLog poly a) = a s *^ IntOfLog k p = IntOfLog (s * k) (s *^ p) }}} {{{ ghc: panic! (the 'impossible' happened) (GHC version 8.1.20161206 for x86_64-unknown-linux): ASSERT failed! $dAdditiveGroup_aIU Call stack: CallStack (from HasCallStack): prettyCurrentCallStack, called at compiler/utils/Outputable.hs:1114:58 in ghc:Outputable callStackDoc, called at compiler/utils/Outputable.hs:1163:22 in ghc:Outputable assertPprPanic, called at compiler/stgSyn/CoreToStg.hs:967:78 in ghc:CoreToStg Call stack: CallStack (from HasCallStack): prettyCurrentCallStack, called at compiler/utils/Outputable.hs:1114:58 in ghc:Outputable callStackDoc, called at compiler/utils/Outputable.hs:1118:37 in ghc:Outputable pprPanic, called at compiler/utils/Outputable.hs:1161:5 in ghc:Outputable assertPprPanic, called at compiler/stgSyn/CoreToStg.hs:967:78 in ghc:CoreToStg Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12944 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler