diff options
| author | David Waern <unknown> | 2007-08-29 22:40:23 +0000 | 
|---|---|---|
| committer | David Waern <unknown> | 2007-08-29 22:40:23 +0000 | 
| commit | 658e79eddf0ac941d2719ec0a3aea58f42ef1277 (patch) | |
| tree | 649135576118781ddc77896f81289df5b5699cec /src/Haddock/GHC | |
| parent | c9746ad9a53e84c3a46ff8fd77f0fb3656ca7697 (diff) | |
Major refactoring
Diffstat (limited to 'src/Haddock/GHC')
| -rw-r--r-- | src/Haddock/GHC/Typecheck.hs | 106 | ||||
| -rw-r--r-- | src/Haddock/GHC/Utils.hs | 79 | 
2 files changed, 185 insertions, 0 deletions
diff --git a/src/Haddock/GHC/Typecheck.hs b/src/Haddock/GHC/Typecheck.hs new file mode 100644 index 00000000..e8e291ad --- /dev/null +++ b/src/Haddock/GHC/Typecheck.hs @@ -0,0 +1,106 @@ +-- +-- Haddock - A Haskell Documentation Tool +-- +-- (c) Simon Marlow 2003 +-- + + +module Haddock.GHC.Typecheck ( +  typecheckFiles   +) where + + +import Haddock.Exception +import Haddock.Utils.GHC +import Haddock.Types + +import Data.Maybe +import Control.Monad +import GHC +import Digraph +import BasicTypes +import SrcLoc + + +typecheckFiles :: Session -> [FilePath] -> IO [GhcModule] +typecheckFiles session files = do +  checkedMods <- sortAndCheckModules session files +  return (map mkGhcModule checkedMods) + + +-- | Get the sorted graph of all loaded modules and their dependencies +getSortedModuleGraph :: Session -> IO [(Module, FilePath)] +getSortedModuleGraph session = do +  mbModGraph <- depanal session [] True +  moduleGraph <- case mbModGraph of +    Just mg -> return mg +    Nothing -> throwE "Failed to load all modules" +  let +    getModFile    = fromJust . ml_hs_file . ms_location +    sortedGraph   = topSortModuleGraph False moduleGraph Nothing +    sortedModules = concatMap flattenSCC sortedGraph +    modsAndFiles  = [ (ms_mod modsum, getModFile modsum) | +                      modsum <- sortedModules ] +  return modsAndFiles + + +type CheckedMod = (Module, FilePath, FullyCheckedMod) + + +type FullyCheckedMod = (ParsedSource,  +                        RenamedSource,  +                        TypecheckedSource,  +                        ModuleInfo) + + +-- TODO: make it handle cleanup +sortAndCheckModules :: Session -> [FilePath] -> IO [CheckedMod] +sortAndCheckModules session files = do  + +  -- load all argument files + +  targets <- mapM (\f -> guessTarget f Nothing) files +  setTargets session targets  + +  -- compute the dependencies and load them as well + +  allMods <- getSortedModuleGraph session +  targets' <- mapM (\(_, f) -> guessTarget f Nothing) allMods +  setTargets session targets' + +  flag <- load session LoadAllTargets +  when (failed flag) $  +    throwE "Failed to load all needed modules" + +  -- typecheck the argument modules + +  let argMods = filter ((`elem` files) . snd) allMods + +  checkedMods <- forM argMods $ \(mod, file) -> do +    mbMod <- checkModule session (moduleName mod) False +    case mbMod of +      Just (CheckedModule a (Just b) (Just c) (Just d) _)  +        -> return (mod, file, (a,b,c,d)) +      _ -> throwE ("Failed to check module: " ++ moduleString mod) + +  return checkedMods + + +-- | Dig out what we want from the typechecker output +mkGhcModule :: CheckedMod -> GhcModule  +mkGhcModule (mod, file, checkedMod) = GhcModule { +  ghcModule         = mod, +  ghcFilename       = file, +  ghcMbDocOpts      = mbOpts, +  ghcHaddockModInfo = info, +  ghcMbDoc          = mbDoc, +  ghcGroup          = group, +  ghcMbExports      = mbExports, +  ghcExportedNames  = modInfoExports modInfo, +  ghcNamesInScope   = fromJust $ modInfoTopLevelScope modInfo,  +  ghcInstances      = modInfoInstances modInfo +} +  where +    HsModule _ _ _ _ _ mbOpts _ _      = unLoc parsed +    (group, _, mbExports, mbDoc, info) = renamed +    (parsed, renamed, _, modInfo)      = checkedMod diff --git a/src/Haddock/GHC/Utils.hs b/src/Haddock/GHC/Utils.hs new file mode 100644 index 00000000..8e70057f --- /dev/null +++ b/src/Haddock/GHC/Utils.hs @@ -0,0 +1,79 @@ +-- +-- Haddock - A Haskell Documentation Tool +-- +-- (c) Simon Marlow 2003 +-- + + +module Haddock.GHC.Utils where + + +import Debug.Trace +import Data.Char + +import GHC +import HsSyn +import SrcLoc +import HscTypes +import Outputable +import Packages +import UniqFM +import Name + + +-- names + +nameOccString = occNameString . nameOccName  + + +nameSetMod n newMod =  +  mkExternalName (nameUnique n) newMod (nameOccName n) (nameSrcSpan n) + + +nameSetPkg pkgId n =  +  mkExternalName (nameUnique n) (mkModule pkgId (moduleName mod))  +	               (nameOccName n) (nameSrcSpan n) +  where mod = nameModule n + + +-- modules + + +moduleString :: Module -> String +moduleString = moduleNameString . moduleName  + + +mkModuleNoPkg :: String -> Module +mkModuleNoPkg str = mkModule (stringToPackageId "") (mkModuleName str) + + +modulePkgStr = packageIdString . modulePackageId + + +-- misc + + +-- there should be a better way to check this using the GHC API +isConSym n = head (nameOccString n) == ':' +isVarSym n = fstChar /= '_' && not (isConSym n) && (not . isLetter) fstChar +  where fstChar = head (nameOccString n) + + +getMainDeclBinder :: HsDecl name -> Maybe name +getMainDeclBinder (TyClD d) = Just (tcdName d) +getMainDeclBinder (ValD d) +   = case collectAcc d [] of +        []       -> Nothing  +        (name:_) -> Just (unLoc name) +getMainDeclBinder (SigD d) = sigNameNoLoc d +getMainDeclBinder (ForD (ForeignImport name _ _)) = Just (unLoc name) +getMainDeclBinder (ForD (ForeignExport name _ _)) = Nothing +getMainDeclBinder _ = Nothing + + +-- To keep if if minf_iface is re-introduced +--modInfoName = moduleName . mi_module . minf_iface +--modInfoMod  = mi_module . minf_iface  + + +trace_ppr x y = trace (showSDoc (ppr x)) y  | 
