[GHC] #13499: "Panic: no skolem info" with StaticPointers and typed hole

GHC ghc-devs at haskell.org
Thu Mar 30 10:31:15 UTC 2017


#13499: "Panic: no skolem info" with StaticPointers and typed hole
-------------------------------------+-------------------------------------
        Reporter:  Otini             |                Owner:  (none)
            Type:  bug               |               Status:  new
        Priority:  normal            |            Milestone:
       Component:  Compiler          |              Version:  8.0.1
      Resolution:                    |             Keywords:
                                     |  StaticPointers, hole, skolem, panic
Operating System:  Linux             |         Architecture:  x86_64
 Type of failure:  Compile-time      |  (amd64)
  crash or panic                     |            Test Case:
      Blocked By:                    |             Blocking:
 Related Tickets:                    |  Differential Rev(s):
       Wiki Page:                    |
-------------------------------------+-------------------------------------

Old description:

> When compiling this minimal example:
> {{{#!hs
> {-# LANGUAGE GADTs #-}
> {-# LANGUAGE StaticPointers #-}
>
> import Data.Typeable (Typeable)
> import GHC.StaticPtr (StaticPtr)
>
> f :: Typeable a => StaticPtr (a -> a)
> f = static (\a -> _)
>
> main :: IO ()
> main = return ()
> }}}
>
> I get this output:
>
> {{{
> Bug.hs:8:19: error:ghc: panic! (the 'impossible' happened)
>   (GHC version 8.0.1 for x86_64-unknown-linux):
>         No skolem info: a_aJo[sk]
>
> Please report this as a GHC bug:  http://www.haskell.org/ghc/reportabug
> }}}
>
> Unlike similar reported bugs, this happens on both 8.0.1 and 8.0.2.

New description:

 When compiling this minimal example:
 {{{#!hs
 {-# LANGUAGE StaticPointers #-}

 import Data.Typeable (Typeable)
 import GHC.StaticPtr (StaticPtr)

 f :: Typeable a => StaticPtr (a -> a)
 f = static (\a -> _)

 main :: IO ()
 main = return ()
 }}}

 I get this output:

 {{{
 Bug.hs:8:19: error:ghc: panic! (the 'impossible' happened)
   (GHC version 8.0.1 for x86_64-unknown-linux):
         No skolem info: a_aJo[sk]

 Please report this as a GHC bug:  http://www.haskell.org/ghc/reportabug
 }}}

 Unlike similar reported bugs, this happens on both 8.0.1 and 8.0.2.

 ''Edit:'' no need to activate GADTs.

--

Comment (by Otini):

 Edit: no need to activate GADTs.

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


More information about the ghc-tickets mailing list