[GHC] #12866: GHC internal error while building darcsden
GHC
ghc-devs at haskell.org
Wed Dec 7 17:11:28 UTC 2016
#12866: GHC internal error while building darcsden
-------------------------------------+-------------------------------------
Reporter: simonmic | Owner:
Type: bug | Status: closed
Priority: normal | Milestone: 8.2.1
Component: Compiler (Type | Version: 8.0.1
checker) |
Resolution: fixed | Keywords:
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: #12867 | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Changes (by RyanGlScott):
* status: new => closed
* resolution: => fixed
* related: => #12867
Comment:
Here's (what I believe to be) a minimal test case:
{{{#!hs
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE ConstraintKinds #-}
-- {-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE ImplicitParams #-}
module T12866 where
import Control.Monad.IO.Class
type BT bt = (BackendTransient bt, ?backendTransient :: bt)
type BTIO bt = (BT bt, MonadIO (BackendTransientM bt))
class (Functor (BackendTransientM bt), Monad (BackendTransientM bt))
=> BackendTransient bt where
type BackendTransientM bt :: * -> *
}}}
Running this with GHC 8.0.1/8.0.2 yields:
{{{
[1 of 1] Compiling T12866 ( Bug.hs, interpreted )
Bug.hs:11:33: error:
• GHC internal error: ‘BackendTransientM’ is not in scope during type
checking, but it passed the renamer
tcl_env of environment: [a142 :-> Type variable ‘bt’ = bt]
• In the first argument of ‘MonadIO’, namely ‘BackendTransientM bt’
In the type ‘(BT bt, MonadIO (BackendTransientM bt))’
In the type declaration for ‘BTIO’
Bug.hs:13:1: error:
• Non type-variable argument
in the constraint: Functor (BackendTransientM bt)
(Use FlexibleContexts to permit this)
• In the context: (Functor (BackendTransientM bt),
Monad (BackendTransientM bt))
While checking the super-classes of class ‘BackendTransient’
In the class declaration for ‘BackendTransient’
}}}
But in GHC HEAD, there's no internal error:
{{{
[1 of 1] Compiling T12866 ( Bug.hs, interpreted )
Bug.hs:11:1: error:
• Non type-variable argument
in the constraint: MonadIO (BackendTransientM bt)
(Use FlexibleContexts to permit this)
• In the type synonym declaration for ‘BTIO’
Bug.hs:13:1: error:
• Non type-variable argument
in the constraint: Functor (BackendTransientM bt)
(Use FlexibleContexts to permit this)
• In the context: (Functor (BackendTransientM bt),
Monad (BackendTransientM bt))
While checking the super-classes of class ‘BackendTransient’
In the class declaration for ‘BackendTransient’
}}}
The workaround is simple: just enable `FlexibleContexts`. That makes it
compile without issue on GHC 8.0.1, 8.0.2, and HEAD.
For completeness's sake, I was able to reproduce the issue when building
`darcsden` with GHC 8.0.1, and I confirmed that enabling
`FlexibleContexts` at the top of the file made the internal error go away.
I don't have time to build everything again with GHC HEAD, but I think the
story would be pretty similar.
In conclusion, this is a much more elaborate example of #12867.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/12866#comment:5>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list