[GHC] #14649: ghc panic: mergeSATInfo
GHC
ghc-devs at haskell.org
Mon Jan 8 23:16:22 UTC 2018
#14649: ghc panic: mergeSATInfo
-------------------------------------+-------------------------------------
Reporter: tianxiaogu | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 8.2.2
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 panic with option `-O` and `-fstatic-argument-transformation`.
Affected versions include 8.2.2 and HEAD (8.5.20180108)
{{{#!hs
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE PartialTypeSignatures #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
module T12844 where
barWraper :: ('(r,r') ~ Head rngs, Foo rngs) => FooData rngs
barWraper = bar
bar :: (_) => FooData rngs
bar = barWraper
data FooData rngs
class Foo xs where foo :: (Head xs ~ '(r,r')) => FooData xs
type family Head (xs :: [k]) where Head (x ': xs) = x
}}}
Log:
{{{
ghc: panic! (the 'impossible' happened)
(GHC version 8.5.20180108 for x86_64-unknown-linux):
mergeSATInfo
Left:STSTSTSTSTSVSV, Right:STSTSTSTSTSVSC
Call stack:
CallStack (from HasCallStack):
callStackDoc, called at compiler/utils/Outputable.hs:1150:37 in
ghc:Outputable
pprPanic, called at compiler/simplCore/SAT.hs:152:20 in ghc:SAT
Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug
}}}
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/14649>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list