diff --git a/compiler/iface/IfaceSyn.lhs b/compiler/iface/IfaceSyn.lhs
index 8ca6b392aed446304b0578706f0f64dadb134a0e..b5da626296ea51b58beef8c531819521ab8dc3ca 100644
--- a/compiler/iface/IfaceSyn.lhs
+++ b/compiler/iface/IfaceSyn.lhs
@@ -280,7 +280,15 @@ that is what is seen by importing module with --make
 Note [Orphans]: the ifInstOrph and ifRuleOrph fields
 ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
 If a module contains any "orphans", then its interface file is read
-regardless, so that its instances are not missed.
+regardless, so that its instances are not missed. 
+
+ - If an instance is an orphan its ifInstOprh field is Nothing
+   Otherwise ifInstOrph is (Just n) where n is the Name of a
+   local class or tycon that witnesses its non-orphan-hood.
+   This computation is done by MkIface.instanceToIfaceInst
+
+ - Similarly for ifRuleOrph
+   The computation is done by MkIface.coreRuleToIfaceRule
 
 Roughly speaking, an instance is an orphan if its head (after the =>)
 mentions nothing defined in this module.  Functional dependencies
diff --git a/compiler/iface/MkIface.lhs b/compiler/iface/MkIface.lhs
index 008b806cbc23c32eb853e0e335f2d0b206f7bc97..45a905543c967c340ebd954593ad39987bcd260e 100644
--- a/compiler/iface/MkIface.lhs
+++ b/compiler/iface/MkIface.lhs
@@ -650,9 +650,22 @@ type IfaceDeclABI = (Module, IfaceDecl, IfaceDeclExtras)
 
 data IfaceDeclExtras 
   = IfaceIdExtras    Fixity [IfaceRule]
-  | IfaceDataExtras  Fixity [IfaceInstABI] [(Fixity,[IfaceRule])]
-  | IfaceClassExtras Fixity [IfaceInstABI] [(Fixity,[IfaceRule])]
+
+  | IfaceDataExtras  
+       Fixity			-- Fixity of the tycon itself
+       [IfaceInstABI]		-- Local instances of this tycon
+       				-- See Note [Orphans] in IfaceSyn
+       [(Fixity,[IfaceRule])]	-- For each construcotr, fixity and RULES
+
+  | IfaceClassExtras 
+       Fixity			-- Fixity of the class itself
+       [IfaceInstABI] 		-- Local instances of this class *or*
+       				--   of its associated data types
+       				-- See Note [Orphans] in IfaceSyn
+       [(Fixity,[IfaceRule])]	-- For each class method, fixity and RULES
+
   | IfaceSynExtras   Fixity
+
   | IfaceOtherDeclExtras
 
 abiDecl :: IfaceDeclABI -> IfaceDecl
@@ -727,9 +740,12 @@ declExtras fix_fn rule_env inst_env decl
                      IfaceDataExtras (fix_fn n)
                         (map ifDFun $ lookupOccEnvL inst_env n)
                         (map (id_extras . ifConOcc) (visibleIfConDecls cons))
-      IfaceClass{ifSigs=sigs} -> 
+      IfaceClass{ifSigs=sigs, ifATs=ats} -> 
                      IfaceClassExtras (fix_fn n)
-                        (map ifDFun $ lookupOccEnvL inst_env n)
+                        (map ifDFun $ (concatMap (lookupOccEnvL inst_env . ifName) ats)
+                                    ++ lookupOccEnvL inst_env n)
+		           -- Include instances of the associated types
+			   -- as well as instances of the class (Trac #5147)
                         [id_extras op | IfaceClassOp op _ _ <- sigs]
       IfaceSyn{} -> IfaceSynExtras (fix_fn n)
       _other -> IfaceOtherDeclExtras