[GHC] #13102: orphan family instances can leak through the EPS in --make mode

GHC ghc-devs at haskell.org
Wed Feb 8 17:01:39 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):

 Let me try to explain the situation with `OverloadedLists` more clearly.
 I'm just going to talk about the ''class'' instances since there is
 already something subtle going on there.

 Say that a class instance is

 * ''loaded'' if we have read the interface file that contains it; in this
 case into the EPS. I don't think it makes a real difference here, so I'll
 always assume we are talking about instances defined in external packages.

 * ''transitively imported'' from the module `M` that we're compiling if
 `M` imports (directly or indirectly) the module `D` that defines the class
 instance in question.

 * ''visible'' in the module `M` that we're compiling if we are allowed to
 use the instance to solve a constraint while compiling `M`. Clearly an
 instance must be loaded in order to be visible, but otherwise it's our job
 to implement the test for visibility so that it corresponds to the
 semantics that we want.

 The Haskell Report says

 > Thus, an instance declaration is in scope if and only if a chain of
 `import` declarations leads to the module containing the instance
 declaration.

 so we could simply define

 1. A class instance is visible if and only if it is transitively imported.

 However, GHC's implementation is actually

 2. A class instance is visible if and only if ''either'' it is
 transitively imported, ''or'' it is a non-orphan instance: it mentions
 something (a class or type) in the instance head that is defined in the
 same module.

 The intention is that definition 2 is equivalent to definition 1, but
 cheaper to compute as we don't have to carry around a larger set of all
 transitively imported modules, and don't have to do a membership query in
 this set in the common case of a candidate matching instance that is non-
 orphan. See `Note [Instance lookup and orphan instances]`:
 {{{
 Suppose we are compiling a module M, and we have a zillion packages
 loaded, and we are looking up an instance for C (T W).  If we find a
 match in module 'X' from package 'p', should be "in scope"; that is,

   is p:X in the transitive closure of modules imported from M?

 The difficulty is that the "zillion packages" might include ones loaded
 through earlier invocations of the GHC API, or earlier module loads in
 GHCi.
 They might not be in the dependencies of M itself; and if not, the
 instances
 in them should not be visible.  Trac #2182, #8427.

 There are two cases:
   * If the instance is *not an orphan*, then module X defines C, T, or W.
     And in order for those types to be involved in typechecking M, it
     must be that X is in the transitive closure of M's imports.  So we
     can use the instance.

   * If the instance *is an orphan*, the above reasoning does not apply.
     So we keep track of the set of orphan modules transitively below M;
     this is the ie_visible field of InstEnvs, of type
 VisibleOrphanModules.

     If module p:X is in this set, then we can use the instance, otherwise
     we can't.
 }}}

 Now, here's what happens in the situation with `OverloadedLists`. With
 this extension enabled, a list literal `[True]` desugars to a function
 call `fromListN 1 (True : [])`, where the `[]` in the desugaring is the
 constructor of the list type. I call this desugaring, but the reference to
 `fromListN` is really inserted in the renamer (`rnExpr (ExplicitList _ _
 exps) = ...`). `fromListN` is a method of the class `IsList`, which is
 defined in `GHC.Exts`:
 {{{#!hs
 class IsList l where
   type Item l
   fromList  :: [Item l] -> l
   fromListN :: Int -> [Item l] -> l    -- the Int is the length of the
 list
   fromListN _ = fromList
   toList :: l -> [Item l]
 }}}
 The instance for `[a]` is also defined in `GHC.Exts`:
 {{{#!hs
 instance IsList [a] where
   type (Item [a]) = a
   fromList = id
   toList = id
 }}}
 Crucially `GHC.Exts` is ''not'' transitively imported by `Prelude`; so
 typically it will not be transitively imported in a module that uses
 `OverloadedLists`. (You can verify this easily since `GHC.Exts` defines
 instances of the type family `Item`, and it doesn't show up as a family
 instance import of a module that only imports `Prelude`. But remember this
 whole comment is about class instances, not family instances.)

 So suppose we want to type check the program
 {{{#!hs
 {-# LANGUAGE OverloadedLists #-}
 module Ol where
 f :: [Bool]
 f = [True]
 }}}
 It means
 {{{#!hs
 f :: [Bool]
 f = GHC.Exts.fromListN 1 (True : [])
 }}}
 and recall
 {{{#!hs
 fromListN :: IsList l => Int -> [Item l] -> l
 }}}
 So in order to type check `f`, we need to use the instance `IsList [a]`.
 (Let's ignore the issue of knowing that `Item [a] ~ a`, since this comment
 is not about family instance visibility.)

 The instance `IsList [a]` will certainly have been loaded, because we read
 the interface file for `GHC.Exts` in order to find out the type for
 `fromListN`. Now, consider our definitions 1 and 2 of class instance
 visibility. According to definition 1, the instance `IsList [a]` ''should
 not'' be visible because the module `GHC.Exts` in which it is defined is
 not transitively imported by the module we are compiling. However, the
 instance `IsList [a]` is not an orphan! So according to definition 2, the
 instance ''is'' visible.

 The upshot is that GHC treats the instance as visible and accepts the
 program, which is certainly the desired end result; but a strict
 interpretation of the standard says that GHC should reject the program,
 given the way that the `IsList` class is implemented.

 The problem is with this sentence from the Note quoted above:

 > And in order for those types [here `IsList`] to be involved in
 typechecking M, it must be that X is in the transitive closure of M's
 imports.

 It's not true in this example.

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


More information about the ghc-tickets mailing list