diff options
Diffstat (limited to 'haddock-api/src')
| -rw-r--r-- | haddock-api/src/Haddock.hs | 10 | ||||
| -rw-r--r-- | haddock-api/src/Haddock/Backends/Xhtml/Layout.hs | 2 | ||||
| -rw-r--r-- | haddock-api/src/Haddock/Backends/Xhtml/Types.hs | 2 | ||||
| -rw-r--r-- | haddock-api/src/Haddock/Interface/Create.hs | 12 | ||||
| -rw-r--r-- | haddock-api/src/Haddock/InterfaceFile.hs | 8 | ||||
| -rw-r--r-- | haddock-api/src/Haddock/ModuleTree.hs | 6 | ||||
| -rw-r--r-- | haddock-api/src/Haddock/Options.hs | 4 | 
7 files changed, 22 insertions, 22 deletions
| diff --git a/haddock-api/src/Haddock.hs b/haddock-api/src/Haddock.hs index 314458b2..7fc6edd0 100644 --- a/haddock-api/src/Haddock.hs +++ b/haddock-api/src/Haddock.hs @@ -294,8 +294,8 @@ render dflags flags sinceQual qual ifaces installedIfaces extSrcMap = do      allVisibleIfaces = [ i | i <- allIfaces, OptHide `notElem` instOptions i ]      pkgMod           = fmap ifaceMod (listToMaybe ifaces) -    pkgKey           = fmap moduleUnitId pkgMod -    pkgStr           = fmap unitIdString pkgKey +    pkgKey           = fmap moduleUnit pkgMod +    pkgStr           = fmap unitString pkgKey      pkgNameVer       = modulePackageInfo dflags flags pkgMod      pkgName          = fmap (unpackFS . (\(PackageName n) -> n)) (fst pkgNameVer)      sincePkg         = case sinceQual of @@ -312,7 +312,7 @@ render dflags flags sinceQual qual ifaces installedIfaces extSrcMap = do        (Map.map SrcExternal extSrcMap)        (Map.fromList [ (ifaceMod iface, SrcLocal) | iface <- ifaces ]) -    pkgSrcMap = Map.mapKeys moduleUnitId extSrcMap +    pkgSrcMap = Map.mapKeys moduleUnit extSrcMap      pkgSrcMap'        | Flag_HyperlinkedSource `elem` flags        , Just k <- pkgKey @@ -341,11 +341,11 @@ render dflags flags sinceQual qual ifaces installedIfaces extSrcMap = do      -- records the *wired in* identity base.  So untranslate it      -- so that we can service the request.      unwire :: Module -> Module -    unwire m = m { moduleUnitId = unwireUnitId dflags (moduleUnitId m) } +    unwire m = m { moduleUnit = unwireUnit dflags (moduleUnit m) }    reexportedIfaces <- concat `fmap` (for (reexportFlags flags) $ \mod_str -> do      let warn = hPutStrLn stderr . ("Warning: " ++) -    case readP_to_S parseModuleId mod_str of +    case readP_to_S parseHoleyModule mod_str of        [(m, "")]          | Just iface <- Map.lookup m installedMap          -> return [iface] diff --git a/haddock-api/src/Haddock/Backends/Xhtml/Layout.hs b/haddock-api/src/Haddock/Backends/Xhtml/Layout.hs index 21d544cd..dd8b0b18 100644 --- a/haddock-api/src/Haddock/Backends/Xhtml/Layout.hs +++ b/haddock-api/src/Haddock/Backends/Xhtml/Layout.hs @@ -306,7 +306,7 @@ links ((_,_,sourceMap,lineMap), (_,_,maybe_wiki_url)) loc splice mdl' docName@(D          -- 'mdl'' is a way of "overriding" the module. Without it, instances          -- will point to the module defining the class/family, which is wrong.          origMod = fromMaybe (nameModule n) mdl' -        origPkg = moduleUnitId origMod +        origPkg = moduleUnit origMod          fname = case loc of            RealSrcSpan l _ -> unpackFS (srcSpanFile l) diff --git a/haddock-api/src/Haddock/Backends/Xhtml/Types.hs b/haddock-api/src/Haddock/Backends/Xhtml/Types.hs index d1561791..e3fd2d5a 100644 --- a/haddock-api/src/Haddock/Backends/Xhtml/Types.hs +++ b/haddock-api/src/Haddock/Backends/Xhtml/Types.hs @@ -23,7 +23,7 @@ import GHC  -- the base, module and entity URLs for the source code and wiki links. -type SourceURLs = (Maybe FilePath, Maybe FilePath, Map UnitId FilePath, Map UnitId FilePath) +type SourceURLs = (Maybe FilePath, Maybe FilePath, Map Unit FilePath, Map Unit FilePath)  type WikiURLs = (Maybe FilePath, Maybe FilePath, Maybe FilePath) diff --git a/haddock-api/src/Haddock/Interface/Create.hs b/haddock-api/src/Haddock/Interface/Create.hs index 7e05e669..53fcc358 100644 --- a/haddock-api/src/Haddock/Interface/Create.hs +++ b/haddock-api/src/Haddock/Interface/Create.hs @@ -221,7 +221,7 @@ mkAliasMap dflags mRenamedSource =               -- them to the user.  We should reuse that information;               -- or at least reuse the renamed imports, which know what               -- they import! -             (fmap Module.fsToUnitId $ +             (fmap Module.fsToUnit $                fmap sl_fs $ ideclPkgQual impDecl)               (case ideclName impDecl of SrcLoc.L _ name -> name),             alias)) @@ -265,7 +265,7 @@ unrestrictedModuleImports idecls =  -- Similar to GHC.lookupModule  -- ezyang: Not really...  lookupModuleDyn :: -  DynFlags -> Maybe UnitId -> ModuleName -> Module +  DynFlags -> Maybe Unit -> ModuleName -> Module  lookupModuleDyn _ (Just pkgId) mdlName =    Module.mkModule pkgId mdlName  lookupModuleDyn dflags Nothing mdlName = @@ -839,7 +839,7 @@ availExportItem is_sig modMap thisMod semMod warnings exportedNames                      Just decl -> return ([decl], (noDocForDecl, availNoDocs avail))                | otherwise ->                  return ([], (noDocForDecl, availNoDocs avail)) -      | Just iface <- M.lookup (semToIdMod (moduleUnitId thisMod) m) modMap +      | Just iface <- M.lookup (semToIdMod (moduleUnit thisMod) m) modMap        , Just ds <- M.lookup n (ifaceDeclMap iface) =            return (ds, lookupDocs avail warnings                              (ifaceDocMap iface) @@ -885,10 +885,10 @@ availNoDocs avail =  -- | Given a 'Module' from a 'Name', convert it into a 'Module' that  -- we can actually find in the 'IfaceMap'. -semToIdMod :: UnitId -> Module -> Module +semToIdMod :: Unit -> Module -> Module  semToIdMod this_uid m      | Module.isHoleModule m = mkModule this_uid (moduleName m) -    | otherwise      = m +    | otherwise             = m  hiDecl :: DynFlags -> Name -> ErrMsgGhc (Maybe (LHsDecl GhcRn))  hiDecl dflags t = do @@ -967,7 +967,7 @@ moduleExport thisMod dflags ifaceMap instIfaceMap expMod =              return []    where      m = mkModule unitId expMod -- Identity module! -    unitId = moduleUnitId thisMod +    unitId = moduleUnit thisMod  -- Note [1]:  ------------ diff --git a/haddock-api/src/Haddock/InterfaceFile.hs b/haddock-api/src/Haddock/InterfaceFile.hs index 4be0bdde..c26ab762 100644 --- a/haddock-api/src/Haddock/InterfaceFile.hs +++ b/haddock-api/src/Haddock/InterfaceFile.hs @@ -58,11 +58,11 @@ ifModule if_ =      [] -> error "empty InterfaceFile"      iface:_ -> instMod iface -ifUnitId :: InterfaceFile -> UnitId +ifUnitId :: InterfaceFile -> Unit  ifUnitId if_ =    case ifInstalledIfaces if_ of      [] -> error "empty InterfaceFile" -    iface:_ -> moduleUnitId $ instMod iface +    iface:_ -> moduleUnit $ instMod iface  binaryInterfaceMagic :: Word32 @@ -319,7 +319,7 @@ getSymbolTable bh namecache = do    return (namecache', arr) -type OnDiskName = (UnitId, ModuleName, OccName) +type OnDiskName = (Unit, ModuleName, OccName)  fromOnDiskName @@ -349,7 +349,7 @@ fromOnDiskName _ nc (pid, mod_name, occ) =  serialiseName :: BinHandle -> Name -> UniqFM (Int,Name) -> IO ()  serialiseName bh name _ = do    let modu = nameModule name -  put_ bh (moduleUnitId modu, moduleName modu, nameOccName name) +  put_ bh (moduleUnit modu, moduleName modu, nameOccName name)  ------------------------------------------------------------------------------- diff --git a/haddock-api/src/Haddock/ModuleTree.hs b/haddock-api/src/Haddock/ModuleTree.hs index de0899fe..3d47e4db 100644 --- a/haddock-api/src/Haddock/ModuleTree.hs +++ b/haddock-api/src/Haddock/ModuleTree.hs @@ -15,7 +15,7 @@ module Haddock.ModuleTree ( ModuleTree(..), mkModuleTree ) where  import Haddock.Types ( MDoc )  import GHC                 ( Name ) -import GHC.Types.Module    ( Module, moduleNameString, moduleName, moduleUnitId, unitIdString ) +import GHC.Types.Module    ( Module, moduleNameString, moduleName, moduleUnit, unitString )  import GHC.Driver.Session  ( DynFlags )  import GHC.Driver.Packages ( lookupUnit, unitPackageIdString ) @@ -29,10 +29,10 @@ mkModuleTree :: DynFlags -> Bool -> [(Module, Maybe (MDoc Name))] -> [ModuleTree  mkModuleTree dflags showPkgs mods =    foldr fn [] [ (mdl, splitModule mdl, modPkg mdl, modSrcPkg mdl, short) | (mdl, short) <- mods ]    where -    modPkg mod_ | showPkgs = Just (unitIdString (moduleUnitId mod_)) +    modPkg mod_ | showPkgs = Just (unitString (moduleUnit mod_))                  | otherwise = Nothing      modSrcPkg mod_ | showPkgs = fmap unitPackageIdString -                                     (lookupUnit dflags (moduleUnitId mod_)) +                                     (lookupUnit dflags (moduleUnit mod_))                     | otherwise = Nothing      fn (m,mod_,pkg,srcPkg,short) = addToTrees mod_ m pkg srcPkg short diff --git a/haddock-api/src/Haddock/Options.hs b/haddock-api/src/Haddock/Options.hs index 0ea1c9e1..e8a7a61b 100644 --- a/haddock-api/src/Haddock/Options.hs +++ b/haddock-api/src/Haddock/Options.hs @@ -45,7 +45,7 @@ import           Data.Version  import           Control.Applicative  import           Distribution.Verbosity  import           GHC.Data.FastString -import           GHC ( DynFlags, Module, moduleUnitId ) +import           GHC ( DynFlags, Module, moduleUnit )  import           Haddock.Types  import           Haddock.Utils  import           GHC.Driver.Packages @@ -382,4 +382,4 @@ modulePackageInfo dflags flags (Just modu) =    , optPackageVersion flags <|> fmap unitPackageVersion pkgDb    )    where -    pkgDb = lookupUnit dflags (moduleUnitId modu) +    pkgDb = lookupUnit dflags (moduleUnit modu) | 
