[GHC] #9036: ghc: panic! Binder's type (SingI Symbol <a String>) /= RHS type (String)
GHC
ghc-devs at haskell.org
Fri Apr 25 22:21:50 UTC 2014
#9036: ghc: panic! Binder's type (SingI Symbol <a String>) /= RHS type (String)
---------------------------------------+--------------------------------
Reporter: ntc2 | Owner:
Type: bug | Status: closed
Priority: normal | Milestone:
Component: Compiler | Version: 7.6.3
Resolution: fixed | Keywords: GHC.TypeLits
Operating System: Linux | Architecture: x86
Type of failure: Compile-time crash | Difficulty: Unknown
Test Case: | Blocked By:
Blocking: | Related Tickets:
---------------------------------------+--------------------------------
Changes (by monoidal):
* status: new => closed
* resolution: => fixed
Comment:
I reduced your program to a single file
{{{
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE TypeFamilies #-}
module Debug.Trace.LogTree.Test where
class UncurryM t where
type GetMonad t :: * -> *
class Curry a b where
type Curried a b :: *
gSimple :: String -> String -> [String]
gSimple = simpleLogger (return ())
simpleLogger :: Maybe (GetMonad t after) -> t `Curried` [t]
simpleLogger _ _ = undefined
}}}
which compiled with -O gives the same error in 7.6.3 but 7.8.2 gives a
typecheck error. I believe this is another instance of bugs #7729, #8142,
#8227. So, the issue is fixed in 7.8 and since 7.6 is not actively
developed, I'm closing the ticket.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/9036#comment:3>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list