[GHC] #12634: Panic with piResultTys1

GHC ghc-devs at haskell.org
Wed Sep 28 03:59:08 UTC 2016


#12634: Panic with piResultTys1
-------------------------------------+-------------------------------------
           Reporter:  crockeea       |             Owner:
               Type:  bug            |            Status:  new
           Priority:  normal         |         Milestone:
          Component:  Compiler       |           Version:  8.0.1
           Keywords:                 |  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:
-------------------------------------+-------------------------------------
 {{{
 {-# LANGUAGE DataKinds           #-}
 {-# LANGUAGE ScopedTypeVariables #-}

 twacePowDec :: t m' r -> t m r
 twacePowDec = undefined

 data Bench a

 bench :: (a -> b) -> a -> Bench params
 bench f = undefined

 bench_twacePow :: forall t m m' r . _ => t m' r -> Bench '(t,m,m',r)
 bench_twacePow = bench (twacePowDec :: t m' r -> t m r)
 }}}

 produces (in GHCi):


 {{{
 GHCi, version 8.0.1: http://www.haskell.org/ghc/  :? for help
 [1 of 1] Compiling Main             ( Bug.hs, interpreted )

 Bug.hs:13:58: error:
     • Expected a type, but
       ‘'(t, m, m', r)’ has kind
       ‘(k1 -> k2 -> *, k0, k1, k2)’
     • In the first argument of ‘Bench’, namely ‘'(t, m, m', r)’
       In the type ‘t m' r -> Bench '(t, m, m', r)’

 Bug.hs:14:52: error:
     • Expected kind ‘k1’, but ‘m’ has kind ‘k0’
     • In the first argument of ‘t’, namely ‘m’
       In an expression type signature: t m' r -> t m r
       In the first argument of ‘bench’, namely
         ‘(twacePowDec :: t m' r -> t m r)’
     • Relevant bindings includeghc: panic! (the 'impossible' happened)
   (GHC version 8.0.1 for x86_64-unknown-linux):
         piResultTys1
   k_a18K[tau:3]
   [m'_a17U[sk], r_a17V[sk]]
 }}}


 The intent was to use this code with `-XPartialTypeSignatures`, but the
 bug occurs with or without that extension.

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


More information about the ghc-tickets mailing list