-- -- Haddock - A Haskell Documentation Tool -- -- (c) Simon Marlow 2003 -- -- Here we build the actual module interfaces. By interface we mean the -- information that is used to render a Haddock page for a module. Parts of -- this information is also stored in the interface files. module Haddock.Interface ( createInterfaces ) where import Haddock.DocName import Haddock.Interface.Create import Haddock.Interface.AttachInstances import Haddock.Interface.Rename import Haddock.Types import Haddock.Options import Haddock.GHC.Utils import qualified Data.Map as Map import Data.Map (Map) import Data.List import Control.Monad import Name -- | Turn a topologically sorted list of GhcModules into interfaces. Also -- return the home link environment created in the process, and any error -- messages. createInterfaces :: [GhcModule] -> LinkEnv -> [Flag] -> ([Interface], LinkEnv, [ErrMsg]) createInterfaces modules externalLinks flags = (interfaces, homeLinks, messages) where ((interfaces, homeLinks), messages) = runWriter $ do -- part 1, create the interfaces interfaces <- createInterfaces' modules flags -- part 2, build the link environment let homeLinks = buildHomeLinks interfaces let links = homeLinks `Map.union` externalLinks let allNames = Map.keys links -- part 3, attach the instances let interfaces' = attachInstances interfaces allNames -- part 3, rename the interfaces let warnings = Flag_NoWarnings `notElem` flags interfaces'' <- mapM (renameInterface links warnings) interfaces' return (interfaces'', homeLinks) createInterfaces' :: [GhcModule] -> [Flag] -> ErrMsgM [Interface] createInterfaces' modules flags = do resultMap <- foldM addInterface Map.empty modules return (Map.elems resultMap) where addInterface :: ModuleMap -> GhcModule -> ErrMsgM ModuleMap addInterface map mod = do interface <- createInterface mod flags map return $ Map.insert (ifaceMod interface) interface map -- | Build a mapping which for each original name, points to the "best" -- place to link to in the documentation. For the definition of -- "best", we use "the module nearest the bottom of the dependency -- graph which exports this name", not including hidden modules. When -- there are multiple choices, we pick a random one. -- -- The interfaces are passed in in topologically sorted order, but we start -- by reversing the list so we can do a foldl. buildHomeLinks :: [Interface] -> LinkEnv buildHomeLinks ifaces = foldl upd Map.empty (reverse ifaces) where upd old_env iface | OptHide `elem` ifaceOptions iface = old_env | OptNotHome `elem` ifaceOptions iface = foldl' keep_old old_env exported_names | otherwise = foldl' keep_new old_env exported_names where exported_names = ifaceVisibleExports iface mod = ifaceMod iface keep_old env n = Map.insertWith (\new old -> old) n mod env keep_new env n = Map.insert n mod env