never executed always true always false
    1 {-# LANGUAGE DataKinds #-}
    2 {-# LANGUAGE TypeFamilies #-}
    3 {-# LANGUAGE FlexibleContexts #-}
    4 {-# LANGUAGE FlexibleInstances #-}
    5 {-# LANGUAGE UndecidableInstances #-}
    6 
    7 module GHC.Unit.Module.ModIface
    8    ( ModIface
    9    , ModIface_ (..)
   10    , PartialModIface
   11    , ModIfaceBackend (..)
   12    , IfaceDeclExts
   13    , IfaceBackendExts
   14    , IfaceExport
   15    , WhetherHasOrphans
   16    , WhetherHasFamInst
   17    , mi_boot
   18    , mi_fix
   19    , mi_semantic_module
   20    , mi_free_holes
   21    , mi_mnwib
   22    , renameFreeHoles
   23    , emptyPartialModIface
   24    , emptyFullModIface
   25    , mkIfaceHashCache
   26    , emptyIfaceHashCache
   27    , forceModIface
   28    )
   29 where
   30 
   31 import GHC.Prelude
   32 
   33 import GHC.Hs
   34 
   35 import GHC.Iface.Syntax
   36 import GHC.Iface.Ext.Fields
   37 
   38 import GHC.Unit
   39 import GHC.Unit.Module.Deps
   40 import GHC.Unit.Module.Warnings
   41 
   42 import GHC.Types.Avail
   43 import GHC.Types.Fixity
   44 import GHC.Types.Fixity.Env
   45 import GHC.Types.HpcInfo
   46 import GHC.Types.Name
   47 import GHC.Types.Name.Reader
   48 import GHC.Types.SafeHaskell
   49 import GHC.Types.SourceFile
   50 import GHC.Types.Unique.DSet
   51 import GHC.Types.Unique.FM
   52 
   53 import GHC.Data.Maybe
   54 
   55 import GHC.Utils.Fingerprint
   56 import GHC.Utils.Binary
   57 
   58 import Control.DeepSeq
   59 import Control.Exception
   60 
   61 {- Note [Interface file stages]
   62    ~~~~~~~~~~~~~~~~~~~~~~~~~~~~
   63 
   64 Interface files have two possible stages.
   65 
   66 * A partial stage built from the result of the core pipeline.
   67 * A fully instantiated form. Which also includes fingerprints and
   68   potentially information provided by backends.
   69 
   70 We can build a full interface file two ways:
   71 * Directly from a partial one:
   72   Then we omit backend information and mostly compute fingerprints.
   73 * From a partial one + information produced by a backend.
   74   Then we store the provided information and fingerprint both.
   75 -}
   76 
   77 type PartialModIface = ModIface_ 'ModIfaceCore
   78 type ModIface = ModIface_ 'ModIfaceFinal
   79 
   80 -- | Extends a PartialModIface with information which is either:
   81 -- * Computed after codegen
   82 -- * Or computed just before writing the iface to disk. (Hashes)
   83 -- In order to fully instantiate it.
   84 data ModIfaceBackend = ModIfaceBackend
   85   { mi_iface_hash :: !Fingerprint
   86     -- ^ Hash of the whole interface
   87   , mi_mod_hash :: !Fingerprint
   88     -- ^ Hash of the ABI only
   89   , mi_flag_hash :: !Fingerprint
   90     -- ^ Hash of the important flags used when compiling the module, excluding
   91     -- optimisation flags
   92   , mi_opt_hash :: !Fingerprint
   93     -- ^ Hash of optimisation flags
   94   , mi_hpc_hash :: !Fingerprint
   95     -- ^ Hash of hpc flags
   96   , mi_plugin_hash :: !Fingerprint
   97     -- ^ Hash of plugins
   98   , mi_orphan :: !WhetherHasOrphans
   99     -- ^ Whether this module has orphans
  100   , mi_finsts :: !WhetherHasFamInst
  101     -- ^ Whether this module has family instances. See Note [The type family
  102     -- instance consistency story].
  103   , mi_exp_hash :: !Fingerprint
  104     -- ^ Hash of export list
  105   , mi_orphan_hash :: !Fingerprint
  106     -- ^ Hash for orphan rules, class and family instances combined
  107 
  108     -- Cached environments for easy lookup. These are computed (lazily) from
  109     -- other fields and are not put into the interface file.
  110     -- Not really produced by the backend but there is no need to create them
  111     -- any earlier.
  112   , mi_warn_fn :: !(OccName -> Maybe WarningTxt)
  113     -- ^ Cached lookup for 'mi_warns'
  114   , mi_fix_fn :: !(OccName -> Maybe Fixity)
  115     -- ^ Cached lookup for 'mi_fixities'
  116   , mi_hash_fn :: !(OccName -> Maybe (OccName, Fingerprint))
  117     -- ^ Cached lookup for 'mi_decls'. The @Nothing@ in 'mi_hash_fn' means that
  118     -- the thing isn't in decls. It's useful to know that when seeing if we are
  119     -- up to date wrt. the old interface. The 'OccName' is the parent of the
  120     -- name, if it has one.
  121   }
  122 
  123 data ModIfacePhase
  124   = ModIfaceCore
  125   -- ^ Partial interface built based on output of core pipeline.
  126   | ModIfaceFinal
  127 
  128 -- | Selects a IfaceDecl representation.
  129 -- For fully instantiated interfaces we also maintain
  130 -- a fingerprint, which is used for recompilation checks.
  131 type family IfaceDeclExts (phase :: ModIfacePhase) where
  132   IfaceDeclExts 'ModIfaceCore = IfaceDecl
  133   IfaceDeclExts 'ModIfaceFinal = (Fingerprint, IfaceDecl)
  134 
  135 type family IfaceBackendExts (phase :: ModIfacePhase) where
  136   IfaceBackendExts 'ModIfaceCore = ()
  137   IfaceBackendExts 'ModIfaceFinal = ModIfaceBackend
  138 
  139 
  140 
  141 -- | A 'ModIface' plus a 'ModDetails' summarises everything we know
  142 -- about a compiled module.  The 'ModIface' is the stuff *before* linking,
  143 -- and can be written out to an interface file. The 'ModDetails is after
  144 -- linking and can be completely recovered from just the 'ModIface'.
  145 --
  146 -- When we read an interface file, we also construct a 'ModIface' from it,
  147 -- except that we explicitly make the 'mi_decls' and a few other fields empty;
  148 -- as when reading we consolidate the declarations etc. into a number of indexed
  149 -- maps and environments in the 'ExternalPackageState'.
  150 --
  151 -- See Note [Strictness in ModIface] to learn about why some fields are
  152 -- strict and others are not.
  153 data ModIface_ (phase :: ModIfacePhase)
  154   = ModIface {
  155         mi_module     :: !Module,             -- ^ Name of the module we are for
  156         mi_sig_of     :: !(Maybe Module),     -- ^ Are we a sig of another mod?
  157 
  158         mi_hsc_src    :: !HscSource,          -- ^ Boot? Signature?
  159 
  160         mi_deps     :: Dependencies,
  161                 -- ^ The dependencies of the module.  This is
  162                 -- consulted for directly-imported modules, but not
  163                 -- for anything else (hence lazy)
  164 
  165         mi_usages   :: [Usage],
  166                 -- ^ Usages; kept sorted so that it's easy to decide
  167                 -- whether to write a new iface file (changing usages
  168                 -- doesn't affect the hash of this module)
  169                 -- NOT STRICT!  we read this field lazily from the interface file
  170                 -- It is *only* consulted by the recompilation checker
  171 
  172         mi_exports  :: ![IfaceExport],
  173                 -- ^ Exports
  174                 -- Kept sorted by (mod,occ), to make version comparisons easier
  175                 -- Records the modules that are the declaration points for things
  176                 -- exported by this module, and the 'OccName's of those things
  177 
  178 
  179         mi_used_th  :: !Bool,
  180                 -- ^ Module required TH splices when it was compiled.
  181                 -- This disables recompilation avoidance (see #481).
  182 
  183         mi_fixities :: [(OccName,Fixity)],
  184                 -- ^ Fixities
  185                 -- NOT STRICT!  we read this field lazily from the interface file
  186 
  187         mi_warns    :: Warnings,
  188                 -- ^ Warnings
  189                 -- NOT STRICT!  we read this field lazily from the interface file
  190 
  191         mi_anns     :: [IfaceAnnotation],
  192                 -- ^ Annotations
  193                 -- NOT STRICT!  we read this field lazily from the interface file
  194 
  195 
  196         mi_decls    :: [IfaceDeclExts phase],
  197                 -- ^ Type, class and variable declarations
  198                 -- The hash of an Id changes if its fixity or deprecations change
  199                 --      (as well as its type of course)
  200                 -- Ditto data constructors, class operations, except that
  201                 -- the hash of the parent class/tycon changes
  202 
  203         mi_globals  :: !(Maybe GlobalRdrEnv),
  204                 -- ^ Binds all the things defined at the top level in
  205                 -- the /original source/ code for this module. which
  206                 -- is NOT the same as mi_exports, nor mi_decls (which
  207                 -- may contains declarations for things not actually
  208                 -- defined by the user).  Used for GHCi and for inspecting
  209                 -- the contents of modules via the GHC API only.
  210                 --
  211                 -- (We need the source file to figure out the
  212                 -- top-level environment, if we didn't compile this module
  213                 -- from source then this field contains @Nothing@).
  214                 --
  215                 -- Strictly speaking this field should live in the
  216                 -- 'HomeModInfo', but that leads to more plumbing.
  217 
  218                 -- Instance declarations and rules
  219         mi_insts       :: [IfaceClsInst],     -- ^ Sorted class instance
  220         mi_fam_insts   :: [IfaceFamInst],  -- ^ Sorted family instances
  221         mi_rules       :: [IfaceRule],     -- ^ Sorted rules
  222 
  223         mi_hpc       :: !AnyHpcUsage,
  224                 -- ^ True if this program uses Hpc at any point in the program.
  225 
  226         mi_trust     :: !IfaceTrustInfo,
  227                 -- ^ Safe Haskell Trust information for this module.
  228 
  229         mi_trust_pkg :: !Bool,
  230                 -- ^ Do we require the package this module resides in be trusted
  231                 -- to trust this module? This is used for the situation where a
  232                 -- module is Safe (so doesn't require the package be trusted
  233                 -- itself) but imports some trustworthy modules from its own
  234                 -- package (which does require its own package be trusted).
  235                 -- See Note [Trust Own Package] in GHC.Rename.Names
  236         mi_complete_matches :: ![IfaceCompleteMatch],
  237 
  238         mi_doc_hdr :: Maybe HsDocString,
  239                 -- ^ Module header.
  240 
  241         mi_decl_docs :: DeclDocMap,
  242                 -- ^ Docs on declarations.
  243 
  244         mi_arg_docs :: ArgDocMap,
  245                 -- ^ Docs on arguments.
  246 
  247         mi_final_exts :: !(IfaceBackendExts phase),
  248                 -- ^ Either `()` or `ModIfaceBackend` for
  249                 -- a fully instantiated interface.
  250 
  251         mi_ext_fields :: !ExtensibleFields,
  252                 -- ^ Additional optional fields, where the Map key represents
  253                 -- the field name, resulting in a (size, serialized data) pair.
  254                 -- Because the data is intended to be serialized through the
  255                 -- internal `Binary` class (increasing compatibility with types
  256                 -- using `Name` and `FastString`, such as HIE), this format is
  257                 -- chosen over `ByteString`s.
  258                 --
  259 
  260         mi_src_hash :: !Fingerprint
  261                 -- ^ Hash of the .hs source, used for recompilation checking.
  262      }
  263 
  264 {-
  265 Note [Strictness in ModIface]
  266 ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
  267 
  268 The ModIface is the Haskell representation of an interface (.hi) file.
  269 
  270 * During compilation we write out ModIface values to disk for files
  271   that we have just compiled
  272 * For packages that we depend on we load the ModIface from disk.
  273 
  274 Some fields in the ModIface are deliberately lazy because when we read
  275 an interface file we don't always need all the parts. For example, an
  276 interface file contains information about documentation which is often
  277 not needed during compilation. This is achieved using the lazyPut/lazyGet pair.
  278 If the field was strict then we would pointlessly load this information into memory.
  279 
  280 On the other hand, if we create a ModIface but **don't** write it to
  281 disk then to avoid space leaks we need to make sure to deepseq all these lazy fields
  282 because the ModIface might live for a long time (for instance in a GHCi session).
  283 That's why in GHC.Driver.Main.hscMaybeWriteIface there is the call to
  284 forceModIface.
  285 -}
  286 
  287 -- | Old-style accessor for whether or not the ModIface came from an hs-boot
  288 -- file.
  289 mi_boot :: ModIface -> IsBootInterface
  290 mi_boot iface = if mi_hsc_src iface == HsBootFile
  291     then IsBoot
  292     else NotBoot
  293 
  294 mi_mnwib :: ModIface -> ModuleNameWithIsBoot
  295 mi_mnwib iface = GWIB (moduleName $ mi_module iface) (mi_boot iface)
  296 
  297 -- | Lookups up a (possibly cached) fixity from a 'ModIface'. If one cannot be
  298 -- found, 'defaultFixity' is returned instead.
  299 mi_fix :: ModIface -> OccName -> Fixity
  300 mi_fix iface name = mi_fix_fn (mi_final_exts iface) name `orElse` defaultFixity
  301 
  302 -- | The semantic module for this interface; e.g., if it's a interface
  303 -- for a signature, if 'mi_module' is @p[A=<A>]:A@, 'mi_semantic_module'
  304 -- will be @<A>@.
  305 mi_semantic_module :: ModIface_ a -> Module
  306 mi_semantic_module iface = case mi_sig_of iface of
  307                             Nothing -> mi_module iface
  308                             Just mod -> mod
  309 
  310 -- | The "precise" free holes, e.g., the signatures that this
  311 -- 'ModIface' depends on.
  312 mi_free_holes :: ModIface -> UniqDSet ModuleName
  313 mi_free_holes iface =
  314   case getModuleInstantiation (mi_module iface) of
  315     (_, Just indef)
  316         -- A mini-hack: we rely on the fact that 'renameFreeHoles'
  317         -- drops things that aren't holes.
  318         -> renameFreeHoles (mkUniqDSet cands) (instUnitInsts (moduleUnit indef))
  319     _   -> emptyUniqDSet
  320   where
  321     cands = dep_sig_mods $ mi_deps iface
  322 
  323 -- | Given a set of free holes, and a unit identifier, rename
  324 -- the free holes according to the instantiation of the unit
  325 -- identifier.  For example, if we have A and B free, and
  326 -- our unit identity is @p[A=<C>,B=impl:B]@, the renamed free
  327 -- holes are just C.
  328 renameFreeHoles :: UniqDSet ModuleName -> [(ModuleName, Module)] -> UniqDSet ModuleName
  329 renameFreeHoles fhs insts =
  330     unionManyUniqDSets (map lookup_impl (uniqDSetToList fhs))
  331   where
  332     hmap = listToUFM insts
  333     lookup_impl mod_name
  334         | Just mod <- lookupUFM hmap mod_name = moduleFreeHoles mod
  335         -- It wasn't actually a hole
  336         | otherwise                           = emptyUniqDSet
  337 
  338 -- See Note [Strictness in ModIface] about where we use lazyPut vs put
  339 instance Binary ModIface where
  340    put_ bh (ModIface {
  341                  mi_module    = mod,
  342                  mi_sig_of    = sig_of,
  343                  mi_hsc_src   = hsc_src,
  344                  mi_src_hash = _src_hash, -- Don't `put_` this in the instance
  345                                           -- because we are going to write it
  346                                           -- out separately in the actual file
  347                  mi_deps      = deps,
  348                  mi_usages    = usages,
  349                  mi_exports   = exports,
  350                  mi_used_th   = used_th,
  351                  mi_fixities  = fixities,
  352                  mi_warns     = warns,
  353                  mi_anns      = anns,
  354                  mi_decls     = decls,
  355                  mi_insts     = insts,
  356                  mi_fam_insts = fam_insts,
  357                  mi_rules     = rules,
  358                  mi_hpc       = hpc_info,
  359                  mi_trust     = trust,
  360                  mi_trust_pkg = trust_pkg,
  361                  mi_complete_matches = complete_matches,
  362                  mi_doc_hdr   = doc_hdr,
  363                  mi_decl_docs = decl_docs,
  364                  mi_arg_docs  = arg_docs,
  365                  mi_ext_fields = _ext_fields, -- Don't `put_` this in the instance so we
  366                                               -- can deal with it's pointer in the header
  367                                               -- when we write the actual file
  368                  mi_final_exts = ModIfaceBackend {
  369                    mi_iface_hash = iface_hash,
  370                    mi_mod_hash = mod_hash,
  371                    mi_flag_hash = flag_hash,
  372                    mi_opt_hash = opt_hash,
  373                    mi_hpc_hash = hpc_hash,
  374                    mi_plugin_hash = plugin_hash,
  375                    mi_orphan = orphan,
  376                    mi_finsts = hasFamInsts,
  377                    mi_exp_hash = exp_hash,
  378                    mi_orphan_hash = orphan_hash
  379                  }}) = do
  380         put_ bh mod
  381         put_ bh sig_of
  382         put_ bh hsc_src
  383         put_ bh iface_hash
  384         put_ bh mod_hash
  385         put_ bh flag_hash
  386         put_ bh opt_hash
  387         put_ bh hpc_hash
  388         put_ bh plugin_hash
  389         put_ bh orphan
  390         put_ bh hasFamInsts
  391         lazyPut bh deps
  392         lazyPut bh usages
  393         put_ bh exports
  394         put_ bh exp_hash
  395         put_ bh used_th
  396         put_ bh fixities
  397         lazyPut bh warns
  398         lazyPut bh anns
  399         put_ bh decls
  400         put_ bh insts
  401         put_ bh fam_insts
  402         lazyPut bh rules
  403         put_ bh orphan_hash
  404         put_ bh hpc_info
  405         put_ bh trust
  406         put_ bh trust_pkg
  407         put_ bh complete_matches
  408         lazyPut bh doc_hdr
  409         lazyPut bh decl_docs
  410         lazyPut bh arg_docs
  411 
  412    get bh = do
  413         mod         <- get bh
  414         sig_of      <- get bh
  415         hsc_src     <- get bh
  416         iface_hash  <- get bh
  417         mod_hash    <- get bh
  418         flag_hash   <- get bh
  419         opt_hash    <- get bh
  420         hpc_hash    <- get bh
  421         plugin_hash <- get bh
  422         orphan      <- get bh
  423         hasFamInsts <- get bh
  424         deps        <- lazyGet bh
  425         usages      <- {-# SCC "bin_usages" #-} lazyGet bh
  426         exports     <- {-# SCC "bin_exports" #-} get bh
  427         exp_hash    <- get bh
  428         used_th     <- get bh
  429         fixities    <- {-# SCC "bin_fixities" #-} get bh
  430         warns       <- {-# SCC "bin_warns" #-} lazyGet bh
  431         anns        <- {-# SCC "bin_anns" #-} lazyGet bh
  432         decls       <- {-# SCC "bin_tycldecls" #-} get bh
  433         insts       <- {-# SCC "bin_insts" #-} get bh
  434         fam_insts   <- {-# SCC "bin_fam_insts" #-} get bh
  435         rules       <- {-# SCC "bin_rules" #-} lazyGet bh
  436         orphan_hash <- get bh
  437         hpc_info    <- get bh
  438         trust       <- get bh
  439         trust_pkg   <- get bh
  440         complete_matches <- get bh
  441         doc_hdr     <- lazyGet bh
  442         decl_docs   <- lazyGet bh
  443         arg_docs    <- lazyGet bh
  444         return (ModIface {
  445                  mi_module      = mod,
  446                  mi_sig_of      = sig_of,
  447                  mi_hsc_src     = hsc_src,
  448                  mi_src_hash = fingerprint0, -- placeholder because this is dealt
  449                                              -- with specially when the file is read
  450                  mi_deps        = deps,
  451                  mi_usages      = usages,
  452                  mi_exports     = exports,
  453                  mi_used_th     = used_th,
  454                  mi_anns        = anns,
  455                  mi_fixities    = fixities,
  456                  mi_warns       = warns,
  457                  mi_decls       = decls,
  458                  mi_globals     = Nothing,
  459                  mi_insts       = insts,
  460                  mi_fam_insts   = fam_insts,
  461                  mi_rules       = rules,
  462                  mi_hpc         = hpc_info,
  463                  mi_trust       = trust,
  464                  mi_trust_pkg   = trust_pkg,
  465                         -- And build the cached values
  466                  mi_complete_matches = complete_matches,
  467                  mi_doc_hdr     = doc_hdr,
  468                  mi_decl_docs   = decl_docs,
  469                  mi_arg_docs    = arg_docs,
  470                  mi_ext_fields  = emptyExtensibleFields, -- placeholder because this is dealt
  471                                                          -- with specially when the file is read
  472                  mi_final_exts = ModIfaceBackend {
  473                    mi_iface_hash = iface_hash,
  474                    mi_mod_hash = mod_hash,
  475                    mi_flag_hash = flag_hash,
  476                    mi_opt_hash = opt_hash,
  477                    mi_hpc_hash = hpc_hash,
  478                    mi_plugin_hash = plugin_hash,
  479                    mi_orphan = orphan,
  480                    mi_finsts = hasFamInsts,
  481                    mi_exp_hash = exp_hash,
  482                    mi_orphan_hash = orphan_hash,
  483                    mi_warn_fn = mkIfaceWarnCache warns,
  484                    mi_fix_fn = mkIfaceFixCache fixities,
  485                    mi_hash_fn = mkIfaceHashCache decls
  486                  }})
  487 
  488 -- | The original names declared of a certain module that are exported
  489 type IfaceExport = AvailInfo
  490 
  491 emptyPartialModIface :: Module -> PartialModIface
  492 emptyPartialModIface mod
  493   = ModIface { mi_module      = mod,
  494                mi_sig_of      = Nothing,
  495                mi_hsc_src     = HsSrcFile,
  496                mi_src_hash    = fingerprint0,
  497                mi_deps        = noDependencies,
  498                mi_usages      = [],
  499                mi_exports     = [],
  500                mi_used_th     = False,
  501                mi_fixities    = [],
  502                mi_warns       = NoWarnings,
  503                mi_anns        = [],
  504                mi_insts       = [],
  505                mi_fam_insts   = [],
  506                mi_rules       = [],
  507                mi_decls       = [],
  508                mi_globals     = Nothing,
  509                mi_hpc         = False,
  510                mi_trust       = noIfaceTrustInfo,
  511                mi_trust_pkg   = False,
  512                mi_complete_matches = [],
  513                mi_doc_hdr     = Nothing,
  514                mi_decl_docs   = emptyDeclDocMap,
  515                mi_arg_docs    = emptyArgDocMap,
  516                mi_final_exts  = (),
  517                mi_ext_fields  = emptyExtensibleFields
  518              }
  519 
  520 emptyFullModIface :: Module -> ModIface
  521 emptyFullModIface mod =
  522     (emptyPartialModIface mod)
  523       { mi_decls = []
  524       , mi_final_exts = ModIfaceBackend
  525         { mi_iface_hash = fingerprint0,
  526           mi_mod_hash = fingerprint0,
  527           mi_flag_hash = fingerprint0,
  528           mi_opt_hash = fingerprint0,
  529           mi_hpc_hash = fingerprint0,
  530           mi_plugin_hash = fingerprint0,
  531           mi_orphan = False,
  532           mi_finsts = False,
  533           mi_exp_hash = fingerprint0,
  534           mi_orphan_hash = fingerprint0,
  535           mi_warn_fn = emptyIfaceWarnCache,
  536           mi_fix_fn = emptyIfaceFixCache,
  537           mi_hash_fn = emptyIfaceHashCache } }
  538 
  539 -- | Constructs cache for the 'mi_hash_fn' field of a 'ModIface'
  540 mkIfaceHashCache :: [(Fingerprint,IfaceDecl)]
  541                  -> (OccName -> Maybe (OccName, Fingerprint))
  542 mkIfaceHashCache pairs
  543   = \occ -> lookupOccEnv env occ
  544   where
  545     env = foldl' add_decl emptyOccEnv pairs
  546     add_decl env0 (v,d) = foldl' add env0 (ifaceDeclFingerprints v d)
  547       where
  548         add env0 (occ,hash) = extendOccEnv env0 occ (occ,hash)
  549 
  550 emptyIfaceHashCache :: OccName -> Maybe (OccName, Fingerprint)
  551 emptyIfaceHashCache _occ = Nothing
  552 
  553 -- Take care, this instance only forces to the degree necessary to
  554 -- avoid major space leaks.
  555 instance (NFData (IfaceBackendExts (phase :: ModIfacePhase)), NFData (IfaceDeclExts (phase :: ModIfacePhase))) => NFData (ModIface_ phase) where
  556   rnf (ModIface f1 f2 f3 f4 f5 f6 f7 f8 f9 f10 f11 f12
  557                 f13 f14 f15 f16 f17 f18 f19 f20 f21 f22 f23 f24 f25) =
  558     rnf f1 `seq` rnf f2 `seq` f3 `seq` f4 `seq` f5 `seq` f6 `seq` rnf f7 `seq` f8 `seq`
  559     f9 `seq` rnf f10 `seq` rnf f11 `seq` f12 `seq` rnf f13 `seq` rnf f14 `seq` rnf f15 `seq`
  560     rnf f16 `seq` f17 `seq` rnf f18 `seq` rnf f19 `seq` f20 `seq` f21 `seq` f22 `seq` rnf f23
  561     `seq` rnf f24 `seq` f25 `seq` ()
  562 
  563 instance NFData (ModIfaceBackend) where
  564   rnf (ModIfaceBackend f1 f2 f3 f4 f5 f6 f7 f8 f9 f10 f11 f12 f13)
  565     = rnf f1 `seq` rnf f2 `seq` rnf f3 `seq` rnf f4 `seq`
  566       rnf f5 `seq` rnf f6 `seq` rnf f7 `seq` rnf f8 `seq`
  567       rnf f9 `seq` rnf f10 `seq` rnf f11 `seq` rnf f12 `seq` rnf f13
  568 
  569 
  570 forceModIface :: ModIface -> IO ()
  571 forceModIface iface = () <$ (evaluate $ force iface)
  572 
  573 -- | Records whether a module has orphans. An \"orphan\" is one of:
  574 --
  575 -- * An instance declaration in a module other than the definition
  576 --   module for one of the type constructors or classes in the instance head
  577 --
  578 -- * A rewrite rule in a module other than the one defining
  579 --   the function in the head of the rule
  580 --
  581 type WhetherHasOrphans   = Bool
  582 
  583 -- | Does this module define family instances?
  584 type WhetherHasFamInst = Bool
  585 
  586 
  587