[GHC] #11010: Untouchable type, pattern synonyms

GHC ghc-devs at haskell.org
Fri Oct 23 04:48:43 UTC 2015


#11010: Untouchable type, pattern synonyms
------------------------------------+---------------------------------
           Reporter:  Iceland_jack  |             Owner:
               Type:  bug           |            Status:  new
           Priority:  normal        |         Milestone:
          Component:  Compiler      |           Version:  7.10.2
           Keywords:                |  Operating System:  Linux
       Architecture:  x86           |   Type of failure:  None/Unknown
          Test Case:                |        Blocked By:
           Blocking:                |   Related Tickets:
Differential Rev(s):                |         Wiki Page:
------------------------------------+---------------------------------
 GHC panicked while experimenting

 {{{#!hs
 {-# LANGUAGE PatternSynonyms, ExistentialQuantification, GADTSyntax #-}

 module Test where

 data Expr a where
   Fun :: String -> (a -> b) -> (Expr a -> Expr b)

 pattern IntFun :: () => (a ~ Int) => String -> (a -> b) -> (Expr a -> Expr
 b)
 pattern IntFun str f x = Fun str f x

 pattern Suc :: () => (a ~ Int) => Expr a -> Expr Int
 pattern Suc n <- IntFun _     _     n where
         Suc n =  IntFun "suc" (+ 1) n
 }}}

 {{{
 % ghc Test.hs
 [1 of 1] Compiling Test             ( Test.hs, Test.o )

 Test.hs:12:18:
     Couldn't match expected type ‘Int’ with actual type ‘a1’
       ‘a1’ is untouchable
         inside the constraints (a ~ Int)
         bound by the type signature for Suc :: Expr a -> Expr Int
         at Test.hs:12:9-11ghc: panic! (the 'impossible' happened)
   (GHC version 7.10.2 for i386-unknown-linux):
         No skolem info: a1_anA[ssk]

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

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


More information about the ghc-tickets mailing list