PageRenderTime 45ms CodeModel.GetById 18ms RepoModel.GetById 0ms app.codeStats 0ms

/ghc-7.0.4/utils/haddock/src/Haddock/InterfaceFile.hs

http://picorec.googlecode.com/
Haskell | 539 lines | 408 code | 85 blank | 46 comment | 2 complexity | 6997c3096c9214245b8d0a038a19f22c MD5 | raw file
Possible License(s): BSD-3-Clause, BSD-2-Clause
  1. {-# OPTIONS_GHC -fno-warn-orphans #-}
  2. -----------------------------------------------------------------------------
  3. -- |
  4. -- Module : Haddock.InterfaceFile
  5. -- Copyright : (c) David Waern 2006-2009
  6. -- License : BSD-like
  7. --
  8. -- Maintainer : haddock@projects.haskell.org
  9. -- Stability : experimental
  10. -- Portability : portable
  11. --
  12. -- Reading and writing the .haddock interface file
  13. -----------------------------------------------------------------------------
  14. module Haddock.InterfaceFile (
  15. InterfaceFile(..), ifPackageId,
  16. readInterfaceFile, nameCacheFromGhc, freshNameCache, NameCacheAccessor,
  17. writeInterfaceFile
  18. ) where
  19. import Haddock.Types
  20. import Haddock.Utils hiding (out)
  21. import Data.List
  22. import Data.Word
  23. import Data.Array
  24. import Data.IORef
  25. import qualified Data.Map as Map
  26. import Data.Map (Map)
  27. import GHC hiding (NoLink)
  28. import Binary
  29. import Name
  30. import UniqSupply
  31. import UniqFM
  32. import IfaceEnv
  33. import HscTypes
  34. #if MIN_VERSION_ghc(7,1,0)
  35. import GhcMonad (withSession)
  36. #endif
  37. import FastMutInt
  38. import FastString
  39. import Unique
  40. data InterfaceFile = InterfaceFile {
  41. ifLinkEnv :: LinkEnv,
  42. ifInstalledIfaces :: [InstalledInterface]
  43. }
  44. ifPackageId :: InterfaceFile -> PackageId
  45. ifPackageId if_ =
  46. case ifInstalledIfaces if_ of
  47. [] -> error "empty InterfaceFile"
  48. iface:_ -> modulePackageId $ instMod iface
  49. binaryInterfaceMagic :: Word32
  50. binaryInterfaceMagic = 0xD0Cface
  51. -- Since datatypes in the GHC API might change between major versions, and
  52. -- because we store GHC datatypes in our interface files, we need to make sure
  53. -- we version our interface files accordingly.
  54. binaryInterfaceVersion :: Word16
  55. #if __GLASGOW_HASKELL__ == 700
  56. binaryInterfaceVersion = 16
  57. #elif __GLASGOW_HASKELL__ == 701
  58. binaryInterfaceVersion = 16
  59. #else
  60. #error Unknown GHC version
  61. #endif
  62. initBinMemSize :: Int
  63. initBinMemSize = 1024*1024
  64. writeInterfaceFile :: FilePath -> InterfaceFile -> IO ()
  65. writeInterfaceFile filename iface = do
  66. bh0 <- openBinMem initBinMemSize
  67. put_ bh0 binaryInterfaceMagic
  68. put_ bh0 binaryInterfaceVersion
  69. -- remember where the dictionary pointer will go
  70. dict_p_p <- tellBin bh0
  71. put_ bh0 dict_p_p
  72. -- remember where the symbol table pointer will go
  73. symtab_p_p <- tellBin bh0
  74. put_ bh0 symtab_p_p
  75. -- Make some intial state
  76. symtab_next <- newFastMutInt
  77. writeFastMutInt symtab_next 0
  78. symtab_map <- newIORef emptyUFM
  79. let bin_symtab = BinSymbolTable {
  80. bin_symtab_next = symtab_next,
  81. bin_symtab_map = symtab_map }
  82. dict_next_ref <- newFastMutInt
  83. writeFastMutInt dict_next_ref 0
  84. dict_map_ref <- newIORef emptyUFM
  85. let bin_dict = BinDictionary {
  86. bin_dict_next = dict_next_ref,
  87. bin_dict_map = dict_map_ref }
  88. ud <- newWriteState (putName bin_symtab) (putFastString bin_dict)
  89. -- put the main thing
  90. bh <- return $ setUserData bh0 ud
  91. put_ bh iface
  92. -- write the symtab pointer at the front of the file
  93. symtab_p <- tellBin bh
  94. putAt bh symtab_p_p symtab_p
  95. seekBin bh symtab_p
  96. -- write the symbol table itself
  97. symtab_next' <- readFastMutInt symtab_next
  98. symtab_map' <- readIORef symtab_map
  99. putSymbolTable bh symtab_next' symtab_map'
  100. -- write the dictionary pointer at the fornt of the file
  101. dict_p <- tellBin bh
  102. putAt bh dict_p_p dict_p
  103. seekBin bh dict_p
  104. -- write the dictionary itself
  105. dict_next <- readFastMutInt dict_next_ref
  106. dict_map <- readIORef dict_map_ref
  107. putDictionary bh dict_next dict_map
  108. -- and send the result to the file
  109. writeBinMem bh filename
  110. return ()
  111. type NameCacheAccessor m = (m NameCache, NameCache -> m ())
  112. nameCacheFromGhc :: NameCacheAccessor Ghc
  113. nameCacheFromGhc = ( read_from_session , write_to_session )
  114. where
  115. read_from_session = do
  116. ref <- withSession (return . hsc_NC)
  117. liftIO $ readIORef ref
  118. write_to_session nc' = do
  119. ref <- withSession (return . hsc_NC)
  120. liftIO $ writeIORef ref nc'
  121. freshNameCache :: NameCacheAccessor IO
  122. freshNameCache = ( create_fresh_nc , \_ -> return () )
  123. where
  124. create_fresh_nc = do
  125. u <- mkSplitUniqSupply 'a' -- ??
  126. return (initNameCache u [])
  127. -- | Read a Haddock (@.haddock@) interface file. Return either an
  128. -- 'InterfaceFile' or an error message.
  129. --
  130. -- This function can be called in two ways. Within a GHC session it will
  131. -- update the use and update the session's name cache. Outside a GHC session
  132. -- a new empty name cache is used. The function is therefore generic in the
  133. -- monad being used. The exact monad is whichever monad the first
  134. -- argument, the getter and setter of the name cache, requires.
  135. --
  136. readInterfaceFile :: MonadIO m =>
  137. NameCacheAccessor m
  138. -> FilePath -> m (Either String InterfaceFile)
  139. readInterfaceFile (get_name_cache, set_name_cache) filename = do
  140. bh0 <- liftIO $ readBinMem filename
  141. magic <- liftIO $ get bh0
  142. version <- liftIO $ get bh0
  143. case () of
  144. _ | magic /= binaryInterfaceMagic -> return . Left $
  145. "Magic number mismatch: couldn't load interface file: " ++ filename
  146. | version /= binaryInterfaceVersion -> return . Left $
  147. "Interface file is of wrong version: " ++ filename
  148. | otherwise -> do
  149. dict <- get_dictionary bh0
  150. bh1 <- init_handle_user_data bh0 dict
  151. theNC <- get_name_cache
  152. (nc', symtab) <- get_symbol_table bh1 theNC
  153. set_name_cache nc'
  154. -- set the symbol table
  155. let ud' = getUserData bh1
  156. bh2 <- return $! setUserData bh1 ud'{ud_symtab = symtab}
  157. -- load the actual data
  158. iface <- liftIO $ get bh2
  159. return (Right iface)
  160. where
  161. get_dictionary bin_handle = liftIO $ do
  162. dict_p <- get bin_handle
  163. data_p <- tellBin bin_handle
  164. seekBin bin_handle dict_p
  165. dict <- getDictionary bin_handle
  166. seekBin bin_handle data_p
  167. return dict
  168. init_handle_user_data bin_handle dict = liftIO $ do
  169. ud <- newReadState dict
  170. return (setUserData bin_handle ud)
  171. get_symbol_table bh1 theNC = liftIO $ do
  172. symtab_p <- get bh1
  173. data_p' <- tellBin bh1
  174. seekBin bh1 symtab_p
  175. (nc', symtab) <- getSymbolTable bh1 theNC
  176. seekBin bh1 data_p'
  177. return (nc', symtab)
  178. -------------------------------------------------------------------------------
  179. -- * Symbol table
  180. -------------------------------------------------------------------------------
  181. putName :: BinSymbolTable -> BinHandle -> Name -> IO ()
  182. putName BinSymbolTable{
  183. bin_symtab_map = symtab_map_ref,
  184. bin_symtab_next = symtab_next } bh name
  185. = do
  186. symtab_map <- readIORef symtab_map_ref
  187. case lookupUFM symtab_map name of
  188. Just (off,_) -> put_ bh (fromIntegral off :: Word32)
  189. Nothing -> do
  190. off <- readFastMutInt symtab_next
  191. writeFastMutInt symtab_next (off+1)
  192. writeIORef symtab_map_ref
  193. $! addToUFM symtab_map name (off,name)
  194. put_ bh (fromIntegral off :: Word32)
  195. data BinSymbolTable = BinSymbolTable {
  196. bin_symtab_next :: !FastMutInt, -- The next index to use
  197. bin_symtab_map :: !(IORef (UniqFM (Int,Name)))
  198. -- indexed by Name
  199. }
  200. putFastString :: BinDictionary -> BinHandle -> FastString -> IO ()
  201. putFastString BinDictionary { bin_dict_next = j_r,
  202. bin_dict_map = out_r} bh f
  203. = do
  204. out <- readIORef out_r
  205. let unique = getUnique f
  206. case lookupUFM out unique of
  207. Just (j, _) -> put_ bh (fromIntegral j :: Word32)
  208. Nothing -> do
  209. j <- readFastMutInt j_r
  210. put_ bh (fromIntegral j :: Word32)
  211. writeFastMutInt j_r (j + 1)
  212. writeIORef out_r $! addToUFM out unique (j, f)
  213. data BinDictionary = BinDictionary {
  214. bin_dict_next :: !FastMutInt, -- The next index to use
  215. bin_dict_map :: !(IORef (UniqFM (Int,FastString)))
  216. -- indexed by FastString
  217. }
  218. putSymbolTable :: BinHandle -> Int -> UniqFM (Int,Name) -> IO ()
  219. putSymbolTable bh next_off symtab = do
  220. put_ bh next_off
  221. let names = elems (array (0,next_off-1) (eltsUFM symtab))
  222. mapM_ (\n -> serialiseName bh n symtab) names
  223. getSymbolTable :: BinHandle -> NameCache -> IO (NameCache, Array Int Name)
  224. getSymbolTable bh namecache = do
  225. sz <- get bh
  226. od_names <- sequence (replicate sz (get bh))
  227. let
  228. arr = listArray (0,sz-1) names
  229. (namecache', names) =
  230. mapAccumR (fromOnDiskName arr) namecache od_names
  231. --
  232. return (namecache', arr)
  233. type OnDiskName = (PackageId, ModuleName, OccName)
  234. fromOnDiskName
  235. :: Array Int Name
  236. -> NameCache
  237. -> OnDiskName
  238. -> (NameCache, Name)
  239. fromOnDiskName _ nc (pid, mod_name, occ) =
  240. let
  241. modu = mkModule pid mod_name
  242. cache = nsNames nc
  243. in
  244. case lookupOrigNameCache cache modu occ of
  245. Just name -> (nc, name)
  246. Nothing ->
  247. let
  248. us = nsUniqs nc
  249. u = uniqFromSupply us
  250. name = mkExternalName u modu occ noSrcSpan
  251. new_cache = extendNameCache cache modu occ name
  252. in
  253. case splitUniqSupply us of { (us',_) ->
  254. ( nc{ nsUniqs = us', nsNames = new_cache }, name )
  255. }
  256. serialiseName :: BinHandle -> Name -> UniqFM (Int,Name) -> IO ()
  257. serialiseName bh name _ = do
  258. let modu = nameModule name
  259. put_ bh (modulePackageId modu, moduleName modu, nameOccName name)
  260. -------------------------------------------------------------------------------
  261. -- * GhcBinary instances
  262. -------------------------------------------------------------------------------
  263. instance (Ord k, Binary k, Binary v) => Binary (Map k v) where
  264. put_ bh m = put_ bh (Map.toList m)
  265. get bh = fmap (Map.fromList) (get bh)
  266. instance Binary InterfaceFile where
  267. put_ bh (InterfaceFile env ifaces) = do
  268. put_ bh env
  269. put_ bh ifaces
  270. get bh = do
  271. env <- get bh
  272. ifaces <- get bh
  273. return (InterfaceFile env ifaces)
  274. instance Binary InstalledInterface where
  275. put_ bh (InstalledInterface modu info docMap exps visExps opts subMap) = do
  276. put_ bh modu
  277. put_ bh info
  278. put_ bh docMap
  279. put_ bh exps
  280. put_ bh visExps
  281. put_ bh opts
  282. put_ bh subMap
  283. get bh = do
  284. modu <- get bh
  285. info <- get bh
  286. docMap <- get bh
  287. exps <- get bh
  288. visExps <- get bh
  289. opts <- get bh
  290. subMap <- get bh
  291. return (InstalledInterface modu info docMap
  292. exps visExps opts subMap)
  293. instance Binary DocOption where
  294. put_ bh OptHide = do
  295. putByte bh 0
  296. put_ bh OptPrune = do
  297. putByte bh 1
  298. put_ bh OptIgnoreExports = do
  299. putByte bh 2
  300. put_ bh OptNotHome = do
  301. putByte bh 3
  302. get bh = do
  303. h <- getByte bh
  304. case h of
  305. 0 -> do
  306. return OptHide
  307. 1 -> do
  308. return OptPrune
  309. 2 -> do
  310. return OptIgnoreExports
  311. 3 -> do
  312. return OptNotHome
  313. _ -> fail "invalid binary data found"
  314. instance Binary Example where
  315. put_ bh (Example expression result) = do
  316. put_ bh expression
  317. put_ bh result
  318. get bh = do
  319. expression <- get bh
  320. result <- get bh
  321. return (Example expression result)
  322. {-* Generated by DrIFT : Look, but Don't Touch. *-}
  323. instance (Binary id) => Binary (Doc id) where
  324. put_ bh DocEmpty = do
  325. putByte bh 0
  326. put_ bh (DocAppend aa ab) = do
  327. putByte bh 1
  328. put_ bh aa
  329. put_ bh ab
  330. put_ bh (DocString ac) = do
  331. putByte bh 2
  332. put_ bh ac
  333. put_ bh (DocParagraph ad) = do
  334. putByte bh 3
  335. put_ bh ad
  336. put_ bh (DocIdentifier ae) = do
  337. putByte bh 4
  338. put_ bh ae
  339. put_ bh (DocModule af) = do
  340. putByte bh 5
  341. put_ bh af
  342. put_ bh (DocEmphasis ag) = do
  343. putByte bh 6
  344. put_ bh ag
  345. put_ bh (DocMonospaced ah) = do
  346. putByte bh 7
  347. put_ bh ah
  348. put_ bh (DocUnorderedList ai) = do
  349. putByte bh 8
  350. put_ bh ai
  351. put_ bh (DocOrderedList aj) = do
  352. putByte bh 9
  353. put_ bh aj
  354. put_ bh (DocDefList ak) = do
  355. putByte bh 10
  356. put_ bh ak
  357. put_ bh (DocCodeBlock al) = do
  358. putByte bh 11
  359. put_ bh al
  360. put_ bh (DocURL am) = do
  361. putByte bh 12
  362. put_ bh am
  363. put_ bh (DocPic x) = do
  364. putByte bh 13
  365. put_ bh x
  366. put_ bh (DocAName an) = do
  367. putByte bh 14
  368. put_ bh an
  369. put_ bh (DocExamples ao) = do
  370. putByte bh 15
  371. put_ bh ao
  372. get bh = do
  373. h <- getByte bh
  374. case h of
  375. 0 -> do
  376. return DocEmpty
  377. 1 -> do
  378. aa <- get bh
  379. ab <- get bh
  380. return (DocAppend aa ab)
  381. 2 -> do
  382. ac <- get bh
  383. return (DocString ac)
  384. 3 -> do
  385. ad <- get bh
  386. return (DocParagraph ad)
  387. 4 -> do
  388. ae <- get bh
  389. return (DocIdentifier ae)
  390. 5 -> do
  391. af <- get bh
  392. return (DocModule af)
  393. 6 -> do
  394. ag <- get bh
  395. return (DocEmphasis ag)
  396. 7 -> do
  397. ah <- get bh
  398. return (DocMonospaced ah)
  399. 8 -> do
  400. ai <- get bh
  401. return (DocUnorderedList ai)
  402. 9 -> do
  403. aj <- get bh
  404. return (DocOrderedList aj)
  405. 10 -> do
  406. ak <- get bh
  407. return (DocDefList ak)
  408. 11 -> do
  409. al <- get bh
  410. return (DocCodeBlock al)
  411. 12 -> do
  412. am <- get bh
  413. return (DocURL am)
  414. 13 -> do
  415. x <- get bh
  416. return (DocPic x)
  417. 14 -> do
  418. an <- get bh
  419. return (DocAName an)
  420. 15 -> do
  421. ao <- get bh
  422. return (DocExamples ao)
  423. _ -> fail "invalid binary data found"
  424. instance Binary name => Binary (HaddockModInfo name) where
  425. put_ bh hmi = do
  426. put_ bh (hmi_description hmi)
  427. put_ bh (hmi_portability hmi)
  428. put_ bh (hmi_stability hmi)
  429. put_ bh (hmi_maintainer hmi)
  430. get bh = do
  431. descr <- get bh
  432. porta <- get bh
  433. stabi <- get bh
  434. maint <- get bh
  435. return (HaddockModInfo descr porta stabi maint)
  436. instance Binary DocName where
  437. put_ bh (Documented name modu) = do
  438. putByte bh 0
  439. put_ bh name
  440. put_ bh modu
  441. put_ bh (Undocumented name) = do
  442. putByte bh 1
  443. put_ bh name
  444. get bh = do
  445. h <- getByte bh
  446. case h of
  447. 0 -> do
  448. name <- get bh
  449. modu <- get bh
  450. return (Documented name modu)
  451. 1 -> do
  452. name <- get bh
  453. return (Undocumented name)
  454. _ -> error "get DocName: Bad h"