diff --git a/src/Haddock/Backends/DevHelp.hs b/src/Haddock/Backends/DevHelp.hs
index e92037f1276b7fa6f0e3719c5e138cefe807f517..85eb6399e68f9e16e688dd15c1c37332878d24b9 100644
--- a/src/Haddock/Backends/DevHelp.hs
+++ b/src/Haddock/Backends/DevHelp.hs
@@ -21,7 +21,7 @@ import Text.PrettyPrint
 ppDevHelpFile :: FilePath -> String -> Maybe String -> [Interface] -> IO ()
 ppDevHelpFile odir doctitle maybe_package modules = do
   let devHelpFile = package++".devhelp"
-      tree = mkModuleTree True [ (hmod_mod mod, toDescription mod) | mod <- modules ]
+      tree = mkModuleTree True [ (ifaceMod mod, toDescription mod) | mod <- modules ]
       doc =
         text "<?xml version=\"1.0\" encoding=\"utf-8\" standalone=\"no\"?>" $$
         (text "<book xmlns=\"http://www.devhelp.net/book\" title=\""<>text doctitle<>
@@ -64,9 +64,9 @@ ppDevHelpFile odir doctitle maybe_package modules = do
     index :: [(Name, [Module])]
     index = Map.toAscList (foldr getModuleIndex Map.empty modules)
 
-    getModuleIndex hmod fm =
-	Map.unionWith (++) (Map.fromListWith (flip (++)) [(name, [mod]) | name <- hmod_exports hmod, nameModule name == mod]) fm
-	where mod = hmod_mod hmod
+    getModuleIndex iface fm =
+	Map.unionWith (++) (Map.fromListWith (flip (++)) [(name, [mod]) | name <- ifaceExports iface, nameModule name == mod]) fm
+	where mod = ifaceMod iface
 
     ppList :: [(Name, [Module])] -> Doc
     ppList [] = empty
diff --git a/src/Haddock/Backends/Html.hs b/src/Haddock/Backends/Html.hs
index 02a2e5c11f234da6d2eb692e2f1f71830014393f..c44a3e8d97c25ff3230ff8a71b074636b6a68c52 100644
--- a/src/Haddock/Backends/Html.hs
+++ b/src/Haddock/Backends/Html.hs
@@ -65,30 +65,30 @@ ppHtml	:: String
 	-> Maybe String			-- the index URL (--use-index)
 	-> IO ()
 
-ppHtml doctitle maybe_package hmods odir prologue maybe_html_help_format
+ppHtml doctitle maybe_package ifaces odir prologue maybe_html_help_format
 	maybe_source_url maybe_wiki_url
 	maybe_contents_url maybe_index_url =  do
   let
-	visible_hmods = filter visible hmods
-	visible i = OptHide `notElem` hmod_options i
+	visible_ifaces = filter visible ifaces
+	visible i = OptHide `notElem` ifaceOptions i
 
   when (not (isJust maybe_contents_url)) $ 
     ppHtmlContents odir doctitle maybe_package
         maybe_html_help_format maybe_index_url maybe_source_url maybe_wiki_url
-	visible_hmods
+	visible_ifaces
 	False -- we don't want to display the packages in a single-package contents
 	prologue
 
   when (not (isJust maybe_index_url)) $ 
     ppHtmlIndex odir doctitle maybe_package maybe_html_help_format
-      maybe_contents_url maybe_source_url maybe_wiki_url visible_hmods
+      maybe_contents_url maybe_source_url maybe_wiki_url visible_ifaces
     
   when (not (isJust maybe_contents_url && isJust maybe_index_url)) $ 
-	ppHtmlHelpFiles doctitle maybe_package hmods odir maybe_html_help_format []
+	ppHtmlHelpFiles doctitle maybe_package ifaces odir maybe_html_help_format []
 
   mapM_ (ppHtmlModule odir doctitle
 	   maybe_source_url maybe_wiki_url
-	   maybe_contents_url maybe_index_url) visible_hmods
+	   maybe_contents_url maybe_index_url) visible_ifaces
 
 ppHtmlHelpFiles	
     :: String                   -- doctitle
@@ -98,19 +98,19 @@ ppHtmlHelpFiles
 	-> Maybe String             -- the Html Help format (--html-help)
 	-> [FilePath]               -- external packages paths
 	-> IO ()
-ppHtmlHelpFiles doctitle maybe_package hmods odir maybe_html_help_format pkg_paths =  do
+ppHtmlHelpFiles doctitle maybe_package ifaces odir maybe_html_help_format pkg_paths =  do
   let
-	visible_hmods = filter visible hmods
-	visible i = OptHide `notElem` hmod_options i
+	visible_ifaces = filter visible ifaces
+	visible i = OptHide `notElem` ifaceOptions i
 
   -- Generate index and contents page for Html Help if requested
   case maybe_html_help_format of
     Nothing        -> return ()
-    Just "mshelp"  -> ppHHProject odir doctitle maybe_package visible_hmods pkg_paths
+    Just "mshelp"  -> ppHHProject odir doctitle maybe_package visible_ifaces pkg_paths
     Just "mshelp2" -> do
-		ppHH2Files      odir maybe_package visible_hmods pkg_paths
+		ppHH2Files      odir maybe_package visible_ifaces pkg_paths
 		ppHH2Collection odir doctitle maybe_package
-    Just "devhelp" -> ppDevHelpFile odir doctitle maybe_package visible_hmods
+    Just "devhelp" -> ppDevHelpFile odir doctitle maybe_package visible_ifaces
     Just format    -> fail ("The "++format++" format is not implemented")
 
 copyFile :: FilePath -> FilePath -> IO ()
@@ -154,9 +154,9 @@ srcButton :: SourceURLs -> Maybe Interface -> HtmlTable
 srcButton (Just src_base_url, _, _) Nothing =
   topButBox (anchor ! [href src_base_url] << toHtml "Source code")
 
-srcButton (_, Just src_module_url, _) (Just hmod) =
-  let url = spliceURL (Just $ hmod_orig_filename hmod)
-                      (Just $ hmod_mod hmod) Nothing src_module_url
+srcButton (_, Just src_module_url, _) (Just iface) =
+  let url = spliceURL (Just $ ifaceOrigFilename iface)
+                      (Just $ ifaceMod iface) Nothing src_module_url
    in topButBox (anchor ! [href url] << toHtml "Source code")
 
 srcButton _ _ =
@@ -235,7 +235,7 @@ simpleHeader doctitle maybe_contents_url maybe_index_url
 pageHeader :: String -> Interface -> String
     -> SourceURLs -> WikiURLs
     -> Maybe String -> Maybe String -> HtmlTable
-pageHeader mdl hmod doctitle
+pageHeader mdl iface doctitle
            maybe_source_url maybe_wiki_url
            maybe_contents_url maybe_index_url =
   (tda [theclass "topbar"] << 
@@ -244,8 +244,8 @@ pageHeader mdl hmod doctitle
   	image ! [src "haskell_icon.gif", width "16", height 16, alt " "]
        ) <->
        (tda [theclass "title"] << toHtml doctitle) <->
-	srcButton maybe_source_url (Just hmod) <->
-	wikiButton maybe_wiki_url (Just $ hmod_mod hmod) <->
+	srcButton maybe_source_url (Just iface) <->
+	wikiButton maybe_wiki_url (Just $ ifaceMod iface) <->
 	contentsButton maybe_contents_url <->
 	indexButton maybe_index_url
     )
@@ -253,14 +253,14 @@ pageHeader mdl hmod doctitle
    tda [theclass "modulebar"] <<
 	(vanillaTable << (
 	  (td << font ! [size "6"] << toHtml mdl) <->
-	  moduleInfo hmod
+	  moduleInfo iface
 	)
     )
 
 moduleInfo :: Interface -> HtmlTable
-moduleInfo hmod = 
+moduleInfo iface = 
    let
-      info = hmod_info hmod
+      info = ifaceInfo iface
 
       doOneEntry :: (String, (GHC.HaddockModInfo GHC.Name) -> Maybe String) -> Maybe HtmlTable
       doOneEntry (fieldName,field) = case field info of
@@ -297,7 +297,7 @@ ppHtmlContents odir doctitle
   maybe_package maybe_html_help_format maybe_index_url
   maybe_source_url maybe_wiki_url modules showPkgs prologue = do
   let tree = mkModuleTree showPkgs
-         [(hmod_mod mod, toDescription mod) | mod <- modules]
+         [(ifaceMod mod, toDescription mod) | mod <- modules]
       html = 
 	header 
 		(documentCharacterEncoding +++
@@ -481,11 +481,11 @@ ppHtmlIndex odir doctitle maybe_package maybe_html_help_format
   full_index = Map.fromListWith (flip (Map.unionWith (++)))
 		(concat (map getHModIndex modules))
 
-  getHModIndex hmod = 
+  getHModIndex iface = 
     [ (getOccString name, 
-	Map.fromList [(name, [(mdl, name `elem` hmod_visible_exports hmod)])])
-    | name <- hmod_exports hmod ]
-    where mdl = hmod_mod hmod
+	Map.fromList [(name, [(mdl, name `elem` ifaceVisibleExports iface)])])
+    | name <- ifaceExports iface ]
+    where mdl = ifaceMod iface
 
   indexElt :: (String, Map GHC.Name [(Module,Bool)]) -> HtmlTable
   indexElt (str, entities) = 
@@ -527,9 +527,9 @@ ppHtmlModule
 	-> Interface -> IO ()
 ppHtmlModule odir doctitle
   maybe_source_url maybe_wiki_url
-  maybe_contents_url maybe_index_url hmod = do
+  maybe_contents_url maybe_index_url iface = do
   let 
-      mod = hmod_mod hmod
+      mod = ifaceMod iface
       mdl = moduleString mod
       html = 
 	header (documentCharacterEncoding +++
@@ -537,58 +537,60 @@ ppHtmlModule odir doctitle
 		styleSheet +++
 		(script ! [src jsFile, thetype "text/javascript"] $ noHtml)) +++
         body << vanillaTable << (
-	    pageHeader mdl hmod doctitle
+	    pageHeader mdl iface doctitle
 		maybe_source_url maybe_wiki_url
 		maybe_contents_url maybe_index_url </> s15 </>
-	    hmodToHtml maybe_source_url maybe_wiki_url hmod </> s15 </>
+	    ifaceToHtml maybe_source_url maybe_wiki_url iface </> s15 </>
 	    footer
          )
   writeFile (pathJoin [odir, moduleHtmlFile mod]) (renderHtml html)
 
-hmodToHtml :: SourceURLs -> WikiURLs -> Interface -> HtmlTable
-hmodToHtml maybe_source_url maybe_wiki_url hmod
+
+ifaceToHtml :: SourceURLs -> WikiURLs -> Interface -> HtmlTable
+ifaceToHtml maybe_source_url maybe_wiki_url iface
   = abovesSep s15 (contents: description: synopsis: maybe_doc_hdr: bdy)
   where
-        docMap = hmod_rn_doc_map hmod
+    docMap = ifaceRnDocMap iface
  
-	exports = numberSectionHeadings (hmod_rn_export_items hmod)
+    exports = numberSectionHeadings (ifaceRnExportItems iface)
 
-	has_doc (ExportDecl _ _ doc _) = isJust doc
-	has_doc (ExportNoDecl _ _ _) = False
-	has_doc (ExportModule _) = False
-	has_doc _ = True
+    has_doc (ExportDecl _ _ doc _) = isJust doc
+    has_doc (ExportNoDecl _ _ _) = False
+    has_doc (ExportModule _) = False
+    has_doc _ = True
 
-	no_doc_at_all = not (any has_doc exports)
+    no_doc_at_all = not (any has_doc exports)
 
- 	contents = td << vanillaTable << ppModuleContents exports
+    contents = td << vanillaTable << ppModuleContents exports
 
-	description
-          = case hmod_rn_doc hmod of
+    description
+          = case ifaceRnDoc iface of
               Nothing -> Html.emptyTable
               Just doc -> (tda [theclass "section1"] << toHtml "Description") </>
                           docBox (docToHtml doc)
 
 	-- omit the synopsis if there are no documentation annotations at all
-	synopsis
-	  | no_doc_at_all = Html.emptyTable
-	  | otherwise
-	  = (tda [theclass "section1"] << toHtml "Synopsis") </>
-	    s15 </>
+    synopsis
+      | no_doc_at_all = Html.emptyTable
+      | otherwise
+      = (tda [theclass "section1"] << toHtml "Synopsis") </>
+        s15 </>
             (tda [theclass "body"] << vanillaTable <<
-  	        abovesSep s8 (map (processExport True linksInfo docMap)
-			(filter forSummary exports))
-	    )
+            abovesSep s8 (map (processExport True linksInfo docMap)
+            (filter forSummary exports))
+        )
 
 	-- if the documentation doesn't begin with a section header, then
 	-- add one ("Documentation").
-	maybe_doc_hdr
-	    = case exports of		   
-		   [] -> Html.emptyTable
-		   ExportGroup _ _ _ : _ -> Html.emptyTable
-		   _ -> tda [ theclass "section1" ] << toHtml "Documentation"
+    maybe_doc_hdr
+      = case exports of		   
+          [] -> Html.emptyTable
+          ExportGroup _ _ _ : _ -> Html.emptyTable
+          _ -> tda [ theclass "section1" ] << toHtml "Documentation"
+
+    bdy  = map (processExport False linksInfo docMap) exports
+    linksInfo = (maybe_source_url, maybe_wiki_url, iface)
 
-	bdy  = map (processExport False linksInfo docMap) exports
-	linksInfo = (maybe_source_url, maybe_wiki_url, hmod)
 
 ppModuleContents :: [ExportItem DocName] -> HtmlTable
 ppModuleContents exports
@@ -1390,7 +1392,7 @@ declBox html = tda [theclass "decl"] << html
 -- it adds a source and wiki link at the right hand side of the box
 topDeclBox :: LinksInfo -> SrcSpan -> Name -> Html -> HtmlTable
 topDeclBox ((_,_,Nothing), (_,_,Nothing), _) _ _ html = declBox html
-topDeclBox ((_,_,maybe_source_url), (_,_,maybe_wiki_url), hmod)
+topDeclBox ((_,_,maybe_source_url), (_,_,maybe_wiki_url), iface)
            loc name html =
   tda [theclass "topdecl"] <<
   (        table ! [theclass "declbar"] <<
@@ -1413,7 +1415,7 @@ topDeclBox ((_,_,maybe_source_url), (_,_,maybe_wiki_url), hmod)
                                                (Just name) url
                            in anchor ! [href url'] << toHtml "Comments"
   
-        mod = hmod_mod hmod
+        mod = ifaceMod iface
         fname = unpackFS (srcSpanFile loc)
 
 -- a box for displaying an 'argument' (some code which has text to the
diff --git a/src/Haddock/Interface.hs b/src/Haddock/Interface.hs
index b8ee4fe45fd237d58d181bb07c319b2dfaaf9d23..e548f500ce8251a4c2be7fd8d0c364c5cb620046 100644
--- a/src/Haddock/Interface.hs
+++ b/src/Haddock/Interface.hs
@@ -53,7 +53,7 @@ createInterfaces' modules flags = do
     addInterface :: ModuleMap -> GhcModule -> ErrMsgM ModuleMap
     addInterface map mod = do
       interface <- createInterface mod flags map
-      return $ Map.insert (hmod_mod interface) interface map
+      return $ Map.insert (ifaceMod interface) interface map
 
  
 renameInterfaces :: [Interface] -> LinkEnv -> ErrMsgM ([Interface], LinkEnv)
@@ -76,13 +76,13 @@ buildHomeLinks :: [Interface] -> LinkEnv
 buildHomeLinks modules = foldl upd Map.empty (reverse modules)
   where
     upd old_env mod
-      | OptHide    `elem` hmod_options mod = old_env
-      | OptNotHome `elem` hmod_options mod =
+      | OptHide    `elem` ifaceOptions mod = old_env
+      | OptNotHome `elem` ifaceOptions mod =
         foldl' keep_old old_env exported_names
       | otherwise = foldl' keep_new old_env exported_names
       where
-        exported_names = hmod_visible_exports mod
-        modName = hmod_mod mod
+        exported_names = ifaceVisibleExports mod
+        modName = ifaceMod mod
 
         keep_old env n = Map.insertWith (\new old -> old) n
                          (nameSetMod n modName) env
diff --git a/src/Haddock/Interface/AttachInstances.hs b/src/Haddock/Interface/AttachInstances.hs
index 51c531e1e7e2854befcc4dccad2f57fa3ab28c56..8e81d8a6d0e7f3fd45e4df548ade2f84e7b6a8a0 100644
--- a/src/Haddock/Interface/AttachInstances.hs
+++ b/src/Haddock/Interface/AttachInstances.hs
@@ -32,9 +32,9 @@ attachInstances :: [Interface] -> [Interface]
 attachInstances modules = map attach modules
   where
     instMap = fmap (map toHsInstHead . sortImage instHead) $ collectInstances modules
-    attach mod = mod { hmod_export_items = newItems }
+    attach mod = mod { ifaceExportItems = newItems }
       where
-        newItems = map attachExport (hmod_export_items mod)
+        newItems = map attachExport (ifaceExportItems mod)
 
         attachExport (ExportDecl n decl doc _) =
           ExportDecl n decl doc (case Map.lookup n instMap of
@@ -56,7 +56,7 @@ collectInstances modules
   = Map.fromListWith (flip (++)) tyInstPairs `Map.union`
     Map.fromListWith (flip (++)) classInstPairs
   where
-    allInstances = concat (map hmod_instances modules)
+    allInstances = concat (map ifaceInstances modules)
     classInstPairs = [ (is_cls inst, [instanceHead inst]) | 
                        inst <- allInstances ]
     tyInstPairs = [ (tycon, [instanceHead inst]) | inst <- allInstances, 
diff --git a/src/Haddock/Interface/Create.hs b/src/Haddock/Interface/Create.hs
index 161b28511a98de849ac5e5965602b67b7a7941d6..604d49fb711b73002b0df7933057f4c041898c7f 100644
--- a/src/Haddock/Interface/Create.hs
+++ b/src/Haddock/Interface/Create.hs
@@ -82,22 +82,22 @@ createInterface ghcMod flags modMap = do
       | otherwise = exportItems
  
   return Interface {
-    hmod_mod                = mod,
-    hmod_orig_filename      = ghcFilename ghcMod,
-    hmod_info               = ghcHaddockModInfo ghcMod,
-    hmod_doc                = ghcMbDoc ghcMod,
-    hmod_rn_doc             = Nothing,
-    hmod_options            = opts,
-    hmod_locals             = localNames,
-    hmod_doc_map            = docMap,
-    hmod_rn_doc_map         = Map.empty,
-    hmod_sub_map            = subMap,
-    hmod_export_items       = prunedExportItems,
-    hmod_rn_export_items    = [], 
-    hmod_exports            = ghcExportedNames ghcMod,
-    hmod_visible_exports    = visibleNames, 
-    hmod_exported_decl_map  = expDeclMap,
-    hmod_instances          = ghcInstances ghcMod
+    ifaceMod             = mod,
+    ifaceOrigFilename    = ghcFilename ghcMod,
+    ifaceInfo            = ghcHaddockModInfo ghcMod,
+    ifaceDoc             = ghcMbDoc ghcMod,
+    ifaceRnDoc           = Nothing,
+    ifaceOptions         = opts,
+    ifaceLocals          = localNames,
+    ifaceDocMap          = docMap,
+    ifaceRnDocMap        = Map.empty,
+    ifaceSubMap          = subMap,
+    ifaceExportItems     = prunedExportItems,
+    ifaceRnExportItems   = [], 
+    ifaceExports         = ghcExportedNames ghcMod,
+    ifaceVisibleExports  = visibleNames, 
+    ifaceExportedDeclMap = expDeclMap,
+    ifaceInstances       = ghcInstances ghcMod
   }
 
 
@@ -404,9 +404,9 @@ mkExportItems lookupMod this_mod exported_names exportedDeclMap localDeclMap sub
 	| m == this_mod = return (fullContentsOfThisModule this_mod entities localDeclMap docMap)
 	| otherwise = 
 	   case lookupMod m of
-	     Just hmod
-		| OptHide `elem` hmod_options hmod
-			-> return (hmod_export_items hmod)
+	     Just iface
+		| OptHide `elem` ifaceOptions iface
+			-> return (ifaceExportItems iface)
 		| otherwise -> return [ ExportModule m ]
 	     Nothing -> return [] -- already emitted a warning in visibleNames
 
@@ -416,8 +416,8 @@ mkExportItems lookupMod this_mod exported_names exportedDeclMap localDeclMap sub
 	| m == this_mod = (Map.lookup n exportedDeclMap, Map.lookup n docMap)
 	| otherwise = 
 	   case lookupMod m of
-		Just hmod -> (Map.lookup n (hmod_exported_decl_map hmod), 
-                              Map.lookup n (hmod_doc_map hmod))
+		Just iface -> (Map.lookup n (ifaceExportedDeclMap iface), 
+                      Map.lookup n (ifaceDocMap iface))
 		Nothing -> (Nothing, Nothing)
       where
         m = nameModule n
@@ -539,8 +539,8 @@ mkVisibleNames mdl lookupMod localNames scope subMap maybeExps opts declMap
 	| otherwise -> let m' = mkModule (modulePackageId mdl) m in
 	  case lookupMod m' of
 	    Just mod
-		| OptHide `elem` hmod_options mod ->
-		    return (filter (`elem` scope) (hmod_exports mod))
+		| OptHide `elem` ifaceOptions mod ->
+		    return (filter (`elem` scope) (ifaceExports mod))
 		| otherwise -> return []
 	    Nothing
 		-> tell (exportModuleMissingErr mdl m') >> return []
@@ -560,7 +560,7 @@ allSubsOfName :: LookupMod -> Name -> [Name]
 allSubsOfName lookupMod name 
   | isExternalName name =
     case lookupMod (nameModule name) of
-      Just hmod -> Map.findWithDefault [] name (hmod_sub_map hmod)
+      Just iface -> Map.findWithDefault [] name (ifaceSubMap iface)
       Nothing   -> []
   | otherwise =  error $ "Main.allSubsOfName: unexpected unqual'd name"
 
diff --git a/src/Haddock/Interface/Rename.hs b/src/Haddock/Interface/Rename.hs
index a0b92fabda20188309849f7298e130a7d024ab9d..f22f9a2cc920f809b1490b319d2264622169c311 100644
--- a/src/Haddock/Interface/Rename.hs
+++ b/src/Haddock/Interface/Rename.hs
@@ -34,22 +34,22 @@ renameInterface renamingEnv mod =
   -- first create the local env, where every name exported by this module
   -- is mapped to itself, and everything else comes from the global renaming
   -- env
-  let localEnv = foldl fn renamingEnv (hmod_visible_exports mod)
-        where fn env name = Map.insert name (nameSetMod name (hmod_mod mod)) env
+  let localEnv = foldl fn renamingEnv (ifaceVisibleExports mod)
+        where fn env name = Map.insert name (nameSetMod name (ifaceMod mod)) env
       
-      docs = Map.toList (hmod_doc_map mod)
+      docs = Map.toList (ifaceDocMap mod)
       renameMapElem (k,d) = do d' <- renameDoc d; return (k, d') 
 
       -- rename names in the exported declarations to point to things that
       -- are closer to, or maybe even exported by, the current module.
       (renamedExportItems, missingNames1)
-        = runRnFM localEnv (renameExportItems (hmod_export_items mod))
+        = runRnFM localEnv (renameExportItems (ifaceExportItems mod))
 
       (rnDocMap, missingNames2) 
         = runRnFM localEnv (liftM Map.fromList (mapM renameMapElem docs))
 
       (finalModuleDoc, missingNames3)
-        = runRnFM localEnv (renameMaybeDoc (hmod_doc mod))
+        = runRnFM localEnv (renameMaybeDoc (ifaceDoc mod))
 
       -- combine the missing names and filter out the built-ins, which would
       -- otherwise allways be missing. 
@@ -64,14 +64,14 @@ renameInterface renamingEnv mod =
   in do
     -- report things that we couldn't link to. Only do this for non-hidden
     -- modules.
-    when (OptHide `notElem` hmod_options mod && not (null strings)) $
-	  tell ["Warning: " ++ show (ppr (hmod_mod mod) defaultUserStyle) ++ 
+    when (OptHide `notElem` ifaceOptions mod && not (null strings)) $
+	  tell ["Warning: " ++ show (ppr (ifaceMod mod) defaultUserStyle) ++ 
 		": could not find link destinations for:\n"++
 		"   " ++ concat (map (' ':) strings) ]
 
-    return $ mod { hmod_rn_doc = finalModuleDoc,
-                   hmod_rn_doc_map = rnDocMap,
-                   hmod_rn_export_items = renamedExportItems }
+    return $ mod { ifaceRnDoc = finalModuleDoc,
+                   ifaceRnDocMap = rnDocMap,
+                   ifaceRnExportItems = renamedExportItems }
 
 
 --------------------------------------------------------------------------------
diff --git a/src/Haddock/InterfaceFile.hs b/src/Haddock/InterfaceFile.hs
index 228efa7104fe246080b340a3127ea81e63f9a3bd..6441c503cd4e5241bed1199a18a3498e4f777096 100644
--- a/src/Haddock/InterfaceFile.hs
+++ b/src/Haddock/InterfaceFile.hs
@@ -9,7 +9,7 @@ module Haddock.InterfaceFile (
   InterfaceFile(..),
   writeInterfaceFile,
   readInterfaceFile,
-  hmod2interface
+  iface2interface
 ) where
 
 
@@ -55,10 +55,10 @@ instance Binary InterfaceFile where
     env <- get bh
     return (InterfaceFile (Map.fromList env))
 
-hmod2interface hmod = InterfaceMod {
-  imModule      = hmod_mod             hmod,
-  imFilename    = hmod_orig_filename   hmod,
-  imExportItems = hmod_rn_export_items hmod
+iface2interface iface = InterfaceMod {
+  imModule      = ifaceMod             iface,
+  imFilename    = ifaceOrigFilename   iface,
+  imExportItems = ifaceRnExportItems iface
 }
   
 binaryInterfaceMagic = 0xD0Cface :: Word32
diff --git a/src/Haddock/Types.hs b/src/Haddock/Types.hs
index a1e649f62552e40a7da21c08d4648c3d39299957..e704ae4db89af1d775925af7f4a295510d5c8a1e 100644
--- a/src/Haddock/Types.hs
+++ b/src/Haddock/Types.hs
@@ -111,35 +111,35 @@ data GhcModule = GhcModule {
 data Interface = Interface {
 
   -- | A value to identify the module
-  hmod_mod                :: Module,
+  ifaceMod             :: Module,
 
   -- | The original filename for this module
-  hmod_orig_filename      :: FilePath,
+  ifaceOrigFilename    :: FilePath,
 
   -- | Textual information about the module 
-  hmod_info               :: HaddockModInfo Name,
+  ifaceInfo            :: HaddockModInfo Name,
 
   -- | The documentation header for this module
-  hmod_doc                :: Maybe (HsDoc Name),
+  ifaceDoc             :: Maybe (HsDoc Name),
 
   -- | The renamed documentation header for this module
-  hmod_rn_doc             :: Maybe (HsDoc DocName),
+  ifaceRnDoc           :: Maybe (HsDoc DocName),
 
   -- | The Haddock options for this module (prune, ignore-exports, etc)
-  hmod_options            :: [DocOption],
+  ifaceOptions         :: [DocOption],
 
-  hmod_exported_decl_map  :: Map Name (LHsDecl Name),
-  hmod_doc_map            :: Map Name (HsDoc Name),  
-  hmod_rn_doc_map         :: Map Name (HsDoc DocName),
+  ifaceExportedDeclMap :: Map Name (LHsDecl Name),
+  ifaceDocMap          :: Map Name (HsDoc Name),  
+  ifaceRnDocMap        :: Map Name (HsDoc DocName),
 
-  hmod_export_items       :: [ExportItem Name],
-  hmod_rn_export_items    :: [ExportItem DocName],
+  ifaceExportItems     :: [ExportItem Name],
+  ifaceRnExportItems   :: [ExportItem DocName],
 
   -- | All the names that are defined in this module
-  hmod_locals             :: [Name],
+  ifaceLocals          :: [Name],
 
   -- | All the names that are exported by this module
-  hmod_exports            :: [Name],
+  ifaceExports         :: [Name],
 
   -- | All the visible names exported by this module
   -- For a name to be visible, it has to:
@@ -148,12 +148,12 @@ data Interface = Interface {
   --   exception that it can't be from another package.
   -- Basically, a visible name is a name that will show up in the documentation
   -- for this module.
-  hmod_visible_exports    :: [Name],
+  ifaceVisibleExports  :: [Name],
 
-  hmod_sub_map            :: Map Name [Name],
+  ifaceSubMap          :: Map Name [Name],
 
   -- | The instances exported by this module
-  hmod_instances          :: [Instance]
+  ifaceInstances       :: [Instance]
 }
 
 
diff --git a/src/Haddock/Utils.hs b/src/Haddock/Utils.hs
index 81549c90b3b869fedf219a12c4b7815db438f759..502a4795d007dd5a94f234e40801e1f4bfbf287f 100644
--- a/src/Haddock/Utils.hs
+++ b/src/Haddock/Utils.hs
@@ -62,7 +62,7 @@ import System.IO.Unsafe	 ( unsafePerformIO )
 
 -- | extract a module's short description.
 toDescription :: Interface -> Maybe (HsDoc Name)
-toDescription = hmi_description . hmod_info
+toDescription = hmi_description . ifaceInfo
 
 -- ---------------------------------------------------------------------------
 -- Making abstract declarations
diff --git a/src/Main.hs b/src/Main.hs
index b12c7850fc940527b0594e516e61c30f141a9980..980e202345dc540b1a0cb602dc2ff905ec3fe946 100644
--- a/src/Main.hs
+++ b/src/Main.hs
@@ -190,8 +190,8 @@ render flags interfaces = do
   prologue <- getPrologue flags
 
   let 
-    visibleMods = [ m | m <- interfaces, OptHide `notElem` (hmod_options m) ]
-    packageName = (Just . modulePkgStr . hmod_mod . head) visibleMods
+    visibleMods = [ m | m <- interfaces, OptHide `notElem` (ifaceOptions m) ]
+    packageName = (Just . modulePkgStr . ifaceMod . head) visibleMods
  
   when (Flag_GenIndex `elem` flags) $ do
 	ppHtmlIndex odir title packageName maybe_html_help_format