aboutsummaryrefslogtreecommitdiff
path: root/src/Haddock/Typecheck.hs
blob: 088ee8a10940b71921bc6b7c1ee4a9e84aaf6d96 (plain) (blame)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
--
-- Haddock - A Haskell Documentation Tool
--
-- (c) Simon Marlow 2003
--


module Haddock.Typecheck (
  GhcModule(..),
  typecheckFiles  
) where


import Haddock.Exception
import Haddock.Utils.GHC


import Data.Maybe
import Control.Monad
import GHC
import Digraph
import BasicTypes
import SrcLoc


-- | This data structure collects all the information we want about a home 
-- package module that we can get from GHC's typechecker
data GhcModule = GhcModule {
   ghcModule         :: Module,
   ghcFilename       :: FilePath,
   ghcMbDocOpts      :: Maybe String,
   ghcHaddockModInfo :: HaddockModInfo Name,
   ghcMbDoc          :: Maybe (HsDoc Name),
   ghcGroup          :: HsGroup Name,
   ghcMbExports      :: Maybe [LIE Name],
   ghcExportedNames  :: [Name],
   ghcNamesInScope   :: [Name],
   ghcInstances      :: [Instance]
}


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