[GHC] #12158: ghc: panic! (the 'impossible' happened) translateConPatVec: lookup

GHC ghc-devs at haskell.org
Sat Feb 11 14:56:28 UTC 2017


#12158: ghc: panic! (the 'impossible' happened)  translateConPatVec: lookup
-------------------------------------+-------------------------------------
        Reporter:  wozgonon          |                Owner:  gkaracha
            Type:  bug               |               Status:  new
        Priority:  normal            |            Milestone:
       Component:  GHCi              |              Version:  8.0.1
      Resolution:                    |             Keywords:
                                     |  PatternMatchWarnings
Operating System:  Unknown/Multiple  |         Architecture:
 Type of failure:  Compile-time      |  Unknown/Multiple
  crash                              |            Test Case:
      Blocked By:                    |             Blocking:
 Related Tickets:                    |  Differential Rev(s):
       Wiki Page:                    |
-------------------------------------+-------------------------------------

Comment (by p1neapple):

 Another variant with this or a related bug:
 Importing a data constructor with named fields, but only the constructor,
 and destructing an object of that; with another constructor of the same
 name as one not imported in scope also crashes GHC, see code, try to
 compile Test.hs: {{{determinize}}} leads to a panic.

 {{{
 -- File NonDeterministicAutomaton.hs:
 {-# LANGUAGE GADTs #-}
 module NonDeterministicAutomaton where
 import qualified Data.Set as DS

 data NonDeterministicAutomaton s a where
   NA :: (Monoid s) => {
     delta :: DeltaProto a s,
     acc :: DS.Set s,
     states :: DS.Set s
   } -> NonDeterministicAutomaton s a

 type DeltaProto a s = a -> s -> DS.Set s
 }}}

 {{{
 -- file Test.hs:
 {-# LANGUAGE GADTs #-}
 module Test where

 import Prelude hiding (map, filter)
 import NonDeterministicAutomaton (NonDeterministicAutomaton(NA))
 import Data.Set

 data DeterministicAutomaton s a where
   DA :: (Monoid s) => {
     delta :: DeltaProto a s,
     acc :: Set s,
     states :: Set s
   } -> DeterministicAutomaton s a

 type DeltaProto a s = a -> s -> s

 determinize :: (Eq s, Ord s) => NonDeterministicAutomaton s a ->
 DeterministicAutomaton (Set s) a
 determinize ( NA { delta = delta0, acc = acc0, states = naStates } ) = DA
 delta' acc' (singleton naStates) where
   acc' = filter (\x -> any (`elem` x) acc0) (singleton naStates)
   delta' a s = empty
 }}}

--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/12158#comment:10>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler


More information about the ghc-tickets mailing list