[GHC] #9780: dep_orphs in Dependencies redundantly records type family orphans
GHC
ghc-devs at haskell.org
Fri Nov 7 08:29:52 UTC 2014
#9780: dep_orphs in Dependencies redundantly records type family orphans
-------------------------------------+-------------------------------------
Reporter: ezyang | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 7.9
Keywords: | Operating System:
Architecture: Unknown/Multiple | Unknown/Multiple
Difficulty: Unknown | Type of failure: Compile-
Blocked By: | time performance bug
Related Tickets: | Test Case:
| Blocking:
| Differential Revisions:
-------------------------------------+-------------------------------------
Currently, there is a comment on `dep_orphs` claiming this:
{{{
, dep_orphs :: [Module]
-- ^ Orphan modules (whether home or external
pkg),
-- *not* including family instance orphans as they
-- are anyway included in 'dep_finsts'
}}}
However, it is not difficult to discover that this is not true:
{{{
[ezyang at hs01 ghc-quick]$ cat A.hs
{-# LANGUAGE TypeFamilies #-}
module A where
type family F a :: *
[ezyang at hs01 ghc-quick]$ cat B.hs
{-# LANGUAGE TypeFamilies #-}
module B where
import A
type instance F Int = Bool
[ezyang at hs01 ghc-quick]$ cat C.hs
module C where
import B
[ezyang at hs01 ghc-quick]$ inplace/bin/ghc-stage2 --show-iface C.hi | grep
orphans
orphans: GHC.Base GHC.Float B
}}}
I'm not sure if the comment or the implementation is wrong. Certainly
`TcRnDriver` would not work if we removed type family orphans from the
list, because we only currently load `imp_orphans` and not `imp_finsts`.
This change occured in this commit:
{{{
commit 8f212ab5307434edf92c7d10fe0df88ccb5cd6ca
Author: Simon Peyton Jones <simonpj at microsoft.com>
Date: Thu May 26 14:30:15 2011 +0100
Rejig the way in which generic default method signatures are checked
- Check GenericSig in tcClassSigs, along with TypeSig
- Add the generic default methods to the type envt
- Look them up via tcLookupId in TcClassDcl.tcDefMeth
Much nicer!
diff --git a/compiler/typecheck/TcRnDriver.lhs
b/compiler/typecheck/TcRnDriver.lhs
index 2542ad3..5aa6959 100644
--- a/compiler/typecheck/TcRnDriver.lhs
+++ b/compiler/typecheck/TcRnDriver.lhs
@@ -245,7 +245,6 @@ tcRnImports hsc_env this_mod import_decls
-- interfaces, so that their rules and instance decls will
be
-- found.
; loadOrphanModules (imp_orphs imports) False
- ; loadOrphanModules (imp_finsts imports) True
-- Check type-familily consistency
; traceRn (text "rn1: checking family instance consistency")
}}}
When did we start adding type family orphans to the list? This commit is
to blame (it states that modules with type family orphans are orphans,
which means that it will get added to orphan module list in `RnNames` when
we import the interface:
{{{
commit 98a642cf29781ebd33994a4ecbea6ef07f89bbed
Author: Simon Peyton Jones <simonpj at microsoft.com>
Date: Tue Jan 3 10:35:08 2012 +0000
Major refactoring of CoAxioms
@@ -619,7 +620,9 @@ addFingerprints hsc_env mb_old_fingerprint iface0
new_decls
mi_exp_hash = export_hash,
mi_orphan_hash = orphan_hash,
mi_flag_hash = flag_hash,
- mi_orphan = not (null orph_rules && null orph_insts
+ mi_orphan = not ( null orph_rules
+ && null orph_insts
+ && null orph_fis
&& null (ifaceVectInfoVar
(mi_vect_info iface0))),
mi_finsts = not . null $ mi_fam_insts iface0,
mi_decls = sorted_decls,
@@ -631,12 +634,9 @@ addFingerprints hsc_env mb_old_fingerprint iface0
new_decls
this_mod = mi_module iface0
dflags = hsc_dflags hsc_env
this_pkg = thisPackage dflags
- (non_orph_insts, orph_insts) = mkOrphMap ifInstOrph (mi_insts iface0)
- (non_orph_rules, orph_rules) = mkOrphMap ifRuleOrph (mi_rules iface0)
- -- See Note [Orphans] in IfaceSyn
- -- ToDo: shouldn't we be splitting fam_insts into orphans and
- -- non-orphans?
- fam_insts = mi_fam_insts iface0
+ (non_orph_insts, orph_insts) = mkOrphMap ifInstOrph (mi_insts
iface0)
+ (non_orph_rules, orph_rules) = mkOrphMap ifRuleOrph (mi_rules
iface0)
+ (non_orph_fis, orph_fis) = mkOrphMap ifFamInstOrph (mi_fam_insts
iface0)
fix_fn = mi_fix_fn iface0
}}}
I think this is probably a legitimate optimization (keeps interface file
smaller), and we try to put it back into effect. The only downside is
we'll try to load in the entire `mi_fam_insts` list (mostly harmless sense
redundant requests on that front will hit the cache); also, it's more
elegant if mi_orph describes orphanness over all orphans.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/9780>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list