[GHC] #13102: orphan family instances can leak through the EPS in --make mode
GHC
ghc-devs at haskell.org
Sat Feb 4 18:11:02 UTC 2017
#13102: orphan family instances can leak through the EPS in --make mode
-------------------------------------+-------------------------------------
Reporter: rwbarton | Owner: rwbarton
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 8.1
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by rwbarton):
> Again this [a type family instance must have been imported if it matches
a lookup] is guaranteed for non-orphan instances.
There's at least one hole in this scheme, from `OverloadedLists`. Consider
this program
{{{#!hs
{-# LANGUAGE OverloadedLists #-}
module Ol where
-- import GHC.Exts
f :: [Bool]
f = [True]
}}}
The literal `[True]` means `GHC.Exts.fromListN 1 (True : [])` where
`GHC.Exts.fromListN :: Int -> [Item l] -> l`. So we can only accept the
program if we have the instance `Item [a] ~ a` in scope. That instance is
defined in `GHC.Exts` along with the `Item` type family. But note that we
never imported `GHC.Exts`; yet the renamer inserted a reference to
`GHC.Exts.Item` directly. This is the root cause of the problem, that the
renamer inserted a reference to something that wasn't imported.
On my branch, the program as above is rejected because the `Item [a] ~ a`
instance is not imported. That's sort of logical, but not the desired
behavior. If you uncomment the `import GHC.Exts` line, then the program is
accepted.
I haven't yet implemented the "optimization" that treats all type family
instances as visible if they are non-orphan. I use quotes because, as seen
above, it's not actually true, and it would change behavior: in this case
it would change it to the desired behavior. Considering the consistency
checking scheme is based on instances that are imported, is it okay to
treat this instance as visible?
I think it is okay in this case, because the ''type family'' `Item` is
defined in the same module that the instances live in. That means it's
impossible for any module to define instances of `Item` without them being
consistency checked against the instances in `GHC.Exts` that are
implicitly globally visible. So, it's still impossible to ever have an
inconsistent set of visible type family instances.
Note that this argument does not just rest on the `Item [a] ~ a` instances
being non-orphan. If we had a globally visible instance that was non-
orphan because it mentioned a type defined in the same module, it would be
possible to write a conflicting instance without importing the former
instance, and then the consistency checking scheme would fail.
So, this is another example of the constraint I mentioned in comment:6: if
`X` is a magic/wired-in thing that can be in scope without being imported,
then type family instances for `X` must be defined in the module which
defines the type family, not in the module which defines `X`.
In fact, I think we can clarify this whole situation just by changing the
definition of orphan slightly. The note [When exactly is an instance decl
an orphan?] says
> Roughly speaking, an instance is an orphan if its head (after the `=>`)
mentions nothing defined in this module.
But I think the real intent is
> an instance is an orphan if its head (after the `=>`) mentions nothing
''that you need to import this module to see''.
For example, you can write the tuple type constructor `(,)` even if you
import nothing at all. So that means that an `instance Foo (,)` should
still be treated as an orphan instance even if it is defined in the module
defining `(,)`.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/13102#comment:10>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list