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

#13102: orphan family instances can leak through the EPS in --make mode -------------------------------------+------------------------------------- Reporter: rwbarton | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.1 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- In --make mode there is a single EPS whose `eps_fam_inst_env` holds all type family instances that have been read from interface files from external packages for any reason. The type checker uses this field pervasively via `tcGetFamInstEnvs`. When compiling multiple files it's fairly easy to set up a situation in which 1. the first module to be compiled `A` loads an interface file `O.hi` from another package containing an orphan family instance (say, because it imports the module directly); 2. a later module `B` uses this instance to reduce a type, even though `B` has no dependency at all on the module `O` defining the instance. (The only tricky bit in arranging this is that since `B` cannot depend on `A`, a little good fortune is needed for GHC to decide to compile `B` after `A`.) Now another module could import `B` and obtain a function whose definition relies on a type family instance that is not visible from `B` at all, compromising type safety. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13102 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13102: orphan family instances can leak through the EPS in --make mode -------------------------------------+------------------------------------- Reporter: rwbarton | Owner: 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: | -------------------------------------+------------------------------------- Changes (by simonpj): * cc: ezyang (added) Comment: Are you sure? It used to be the case that instances simply accumulated, so a module could "see" an instance (of a type class, say) that it didn't import, even transitively. But I belived we fixed that some time ago. I think it's in the call to `hptInstances` in `tcRnImports`. Ah but that's the ''home'' package, and your point is about some external package. Maybe you are right... Can you show how this can compromise type safety. Presumably it's through an un-detected type-family inconsistency? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13102#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13102: orphan family instances can leak through the EPS in --make mode -------------------------------------+------------------------------------- Reporter: rwbarton | Owner: 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 ezyang): I think rwbarton is probably right; looking at the commit that fixed this for instances 4c834fdddf4d44d12039da4d6a2c63a660975b95 it doesn't look like I actually added any code for *family instances*. So we need to apply an analogous fix there. (I'm not sure what hptInstances is doing but I think it is something else?) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13102#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13102: orphan family instances can leak through the EPS in --make mode -------------------------------------+------------------------------------- Reporter: rwbarton | Owner: 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 simonpj): Aha! You are right! The relevant ticket is #2182. One thing unsaid there is that non-orphan instances cannot be a problem because the module defining a non-orphan instance must be in the transitive closure of modules below the one being compiled. It's just orphan modules that we need to take care about. A huge shortcoming is that this very cunning plan has no Note describing the Grand Plan, at least not that I can see. There ought to be one, with references to the note from the scattered bits of code that implement it. It does seem plausible that that the same thing would work for family instances. Hooray. Finally `hptInstances` appears to do the job (including family instances) for the home package, by glomming up all the instances from the home- package modules below this one. But the clever orphan module approach should work for the home package too, so perhaps we can kill off `hptInstances`? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13102#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

Aha! You are right! The relevant ticket is #2182. One thing unsaid
#13102: orphan family instances can leak through the EPS in --make mode -------------------------------------+------------------------------------- Reporter: rwbarton | Owner: 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): Replying to [comment:3 simonpj]: there is that non-orphan instances cannot be a problem because the module defining a non-orphan instance must be in the transitive closure of modules below the one being compiled. It's just orphan modules that we need to take care about. So the logic here is: a non-orphan (class or type family) instance is one which is either an instance of a class/family defined in the same module or an instance that mentions a type constructor defined in the same module. Either way, in order to use the instance both the class/family and the type constructor must be in scope, so we must have actually imported them (rather than obtained them through leakage from compiling another module). The last step is not entirely true since the type constructor might also be in scope by virtue of being a wired-in type that corresponds to Haskell syntax, like a tuple. Then I don't actually have to import anything to be able to write the type. If the module `W` defining a wired-in thing defines an instance of a class defined in another module for that thing, a user program could see the instance without having to import `W`. I don't know whether this currently occurs in base (it seems to at least not happen for type families), but it's what I wanted to add in #13072. Not saying this should block adoption of the cunning plan, just that it is another wrinkle to be aware of. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13102#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13102: orphan family instances can leak through the EPS in --make mode -------------------------------------+------------------------------------- Reporter: rwbarton | Owner: 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 simonpj): There are several issues here. Let's focus on external packages for now. By "instance" I mean type-class instance or family instance. 1. Ensuring we have ''enough'' instances. That is, have we loaded `M.hi`, and hence added its instances into the `eps_inst_env`? * For non-orphan instances, that's guaranteed. * Note that it's guaranteed even for wired-in type constructors because we do the `checkWiredInTyCon` or `ifCheckWiredInThing`. * For orphan instances we need to take care; I think we just aggressively load all orphan modules. 2. Ensuring we do not have ''too many'' instances. When doing instance lookup we don't want to "see" any instances that are not transitively below us. * Again this is guaranteed for non-orphan instances. * For orphan instances we use the cunning plan in comment:2. * Wired-in things are below everything so I think it's a non-issue. 3. Checking family-instance consistency. Here I am not so clear, but we should write down the plan. Does that taxonomy help? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13102#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13102: orphan family instances can leak through the EPS in --make mode -------------------------------------+------------------------------------- Reporter: rwbarton | Owner: 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):
Wired-in things are below everything
Right, so this becomes a constraint that we have to adhere to under this plan. And it's a constraint I was intending to violate with the large tuples Generic stuff (tuples are wired-in, and I was going to use `deriving Generic` in the module that defines them). I'm not so happy with that exact idea any more for other reasons, so probably it shouldn't stop us from this plan.
Checking family-instance consistency. Here I am not so clear, but we should write down the plan.
I started writing up the plan in d6fd7922332a16fb958d3bf2c21ed792d12c98a7. Note that there is another point related to your item 2 here, in that (at least in principle) we should only check consistency of the new instances with the instances we transitively import, not any old instances we happen to know about. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13102#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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: | -------------------------------------+------------------------------------- Changes (by rwbarton): * owner: => rwbarton -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13102#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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): This issue also affects `-c` with multiple input files, which GHC builds in order, it seems, making it much easier to test. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13102#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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 Ben Gamari

#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

#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 ezyang): Just popping in: rwbarton, in the overloaded lists case, why don't we just consider `GHC.Exts` as visible always? In fact, we already do something like this for wired in things: see `Note [Loading instances for wired-in things]`. There should only be a fixed number of these... -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13102#comment:11 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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 simonpj):
But I think the real intent is ...
No, not really. You'll see a lot of calls to `checkWiredInTyCon` whose solve purpose is to ensure that that the home module for the wired-in type constructor is loaded, even if you don't need to import the module to bring it into scope. In the example you give,
The literal [True] means GHC.Exts.fromListN 1 (True : [])
OK, but `fromListN` is a known-key `Name` but it is not a wired-in `Id`. So to get `fromListN`'s type GHC is forced to load `GHC.Exts.hi`. So I don't see the problem. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13102#comment:12 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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

#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 ezyang): I don't think it's good to read too much into what Haskell'98 says should be the set of visible instances; after all, Haskell'98 doesn't formalize overloaded syntax. There are a few possible ways to adjust the semantics, but one possibility is to say that if the renamer inserts a reference directly to something (that wasn't imported), that implicitly imports the module that provided that original name. This might be annoying to implement, but anything along these lines should be OK? (Certainly, it's what I would expect!) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13102#comment:14 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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 ezyang): simonpj and I chatted about this, and we came up with a short term and a long term solution. * The short term solution is to special-case GHC.Exts so that it is always visible. This should be pretty easy to do. * But, if we look at how the compiler handles finding instances of wired in things, there is a `checkWiredInTyCon` function which we specifically call in order to bring in the instances for a wired in thing. So really, the desired semantics are, if we call `checkWiredInTyCon` on a `TyCon`, we want to act AS IF we had an implicit import of this `TyCon`. This means checking it for family instance consistency (see #13251) and considering it visible. But now that I think about it, it seems very awkward to actually get this info to the list of visible info, since we won't really bang on the TyCon until we're about to do an instance lookup; might be a little fiddly to get that to work. But the long term solution is something like this: an implicit reference to a wired in thing counts as an import to that defining module. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13102#comment:15 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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): I'm a bit unclear on both parts of the plan. * You write "special-case GHC.Exts so that it is always visible". Is this a code change? Are we keeping definition 2 for visibility of class instances for now? We don't really have to do anything about GHC.Exts for now, because: 1. For class instance lookup, the `IsList` instances are already treated as visible because they are non-orphan. 2. For type family instance lookup, the plan is to apply the same non- orphan rule as for class instance lookup, so the `Item` instances will be treated as visible too. 3. For type family consistency checking, we need to make sure that a. All family instances that are made visible in this way are consistent with other visible instances. But there's no actual problem here, because in order to ''define'' an instance of `IsList` you still need to import `GHC.Exts`, and then `GHC.Exts` will be in the set of transitively imported family instance modules that gets checked for consistency. (The way there could have been a problem here is if the instances in question were non-orphan because they defined an instance that mentions a type defined in the module, of a type family that is defined in another module.) b. Since the desugarer is going to insert a call to `GHC.Exts.fromListN` into our module `M`, we also need to make sure that the definition of `fromListN` doesn't depend on some other type family instances that were visible in `GHC.Exts`, which might conflict with ones that are visible in our module `M`. But `fromListN` is just a class method, so surely there's no problem there either. In short, `GHC.Exts` is special-cased in the correctness proof, not in the compiler. But there could be other situations in which the arguments of 3a and 3b don't apply, so a better long-term plan is in order. And #13251 already gives an example. * "But, if we look at how the compiler handles finding instances of wired in things"... This sounds reasonable, but the problem here is not just about wired-in things. `IsList` is known-key, not wired-in; and the example using TH in #13251 is neither. In any case, since #13251 is its own ticket, I'll continue here with the short-term plan of using the same rules for type family instance visibility as for class instance visibility. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13102#comment:16 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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 ezyang): * I think there are two possible cases where code change would be necessary (but I don't think any of them actually apply): - If GHC.Exts defined orphans, we should still treat those orphans as visible. But I don't think we have any orphans. Would be good to check. - You are right that one can't define an instance of IsList without importing it, so we should be able to get away without the check. And evidently this doesn't apply if GHC.Exts does have orphans, because that means we can define an instance without importing GHC.Exts * Yes, I guess we have to handle known-key things. Hmm, we don't call `checkWiredInTyCon` for those, so there might be trouble. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13102#comment:17 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

In any case, since #13251 is its own ticket, I'll continue here with
#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 simonpj): the short-term plan of using the same rules for type family instance visibility as for class instance visibility. Yes that's fine I think. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13102#comment:18 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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 Ben Gamari

#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 Ben Gamari

#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: 9729 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by crockeea): * related: => 9729 Comment: ezyang thought that #9729 might be an example of this bug. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13102#comment:21 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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: #9729 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by crockeea): * related: 9729 => #9729 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13102#comment:22 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC