PageRenderTime 59ms CodeModel.GetById 18ms RepoModel.GetById 0ms app.codeStats 1ms

/compiler/main/GHC.hs

https://github.com/luite/ghc
Haskell | 1430 lines | 864 code | 180 blank | 386 comment | 16 complexity | 303c10bf0a9b124d7ac47dc8cf352a02 MD5 | raw file

Large files files are truncated, but you can click here to view the full file

  1. -- -----------------------------------------------------------------------------
  2. --
  3. -- (c) The University of Glasgow, 2005-2012
  4. --
  5. -- The GHC API
  6. --
  7. -- -----------------------------------------------------------------------------
  8. module GHC (
  9. -- * Initialisation
  10. defaultErrorHandler,
  11. defaultCleanupHandler,
  12. prettyPrintGhcErrors,
  13. -- * GHC Monad
  14. Ghc, GhcT, GhcMonad(..), HscEnv,
  15. runGhc, runGhcT, initGhcMonad,
  16. gcatch, gbracket, gfinally,
  17. printException,
  18. handleSourceError,
  19. needsTemplateHaskell,
  20. -- * Flags and settings
  21. DynFlags(..), GeneralFlag(..), Severity(..), HscTarget(..), gopt,
  22. GhcMode(..), GhcLink(..), defaultObjectTarget,
  23. parseDynamicFlags,
  24. getSessionDynFlags, setSessionDynFlags,
  25. getProgramDynFlags, setProgramDynFlags,
  26. getInteractiveDynFlags, setInteractiveDynFlags,
  27. parseStaticFlags,
  28. -- * Targets
  29. Target(..), TargetId(..), Phase,
  30. setTargets,
  31. getTargets,
  32. addTarget,
  33. removeTarget,
  34. guessTarget,
  35. -- * Loading\/compiling the program
  36. depanal,
  37. load, LoadHowMuch(..), InteractiveImport(..),
  38. SuccessFlag(..), succeeded, failed,
  39. defaultWarnErrLogger, WarnErrLogger,
  40. workingDirectoryChanged,
  41. parseModule, typecheckModule, desugarModule, loadModule,
  42. ParsedModule(..), TypecheckedModule(..), DesugaredModule(..),
  43. TypecheckedSource, ParsedSource, RenamedSource, -- ditto
  44. TypecheckedMod, ParsedMod,
  45. moduleInfo, renamedSource, typecheckedSource,
  46. parsedSource, coreModule,
  47. -- ** Compiling to Core
  48. CoreModule(..),
  49. compileToCoreModule, compileToCoreSimplified,
  50. compileCoreToObj,
  51. -- * Inspecting the module structure of the program
  52. ModuleGraph, ModSummary(..), ms_mod_name, ModLocation(..),
  53. getModSummary,
  54. getModuleGraph,
  55. isLoaded,
  56. topSortModuleGraph,
  57. -- * Inspecting modules
  58. ModuleInfo,
  59. getModuleInfo,
  60. modInfoTyThings,
  61. modInfoTopLevelScope,
  62. modInfoExports,
  63. modInfoInstances,
  64. modInfoIsExportedName,
  65. modInfoLookupName,
  66. modInfoIface,
  67. modInfoSafe,
  68. lookupGlobalName,
  69. findGlobalAnns,
  70. mkPrintUnqualifiedForModule,
  71. ModIface(..),
  72. SafeHaskellMode(..),
  73. -- * Querying the environment
  74. packageDbModules,
  75. -- * Printing
  76. PrintUnqualified, alwaysQualify,
  77. -- * Interactive evaluation
  78. getBindings, getInsts, getPrintUnqual,
  79. findModule, lookupModule,
  80. #ifdef GHCI
  81. isModuleTrusted,
  82. moduleTrustReqs,
  83. setContext, getContext,
  84. getNamesInScope,
  85. getRdrNamesInScope,
  86. getGRE,
  87. moduleIsInterpreted,
  88. getInfo,
  89. exprType,
  90. typeKind,
  91. parseName,
  92. RunResult(..),
  93. runStmt, runStmtWithLocation, runDecls, runDeclsWithLocation,
  94. parseImportDecl, SingleStep(..),
  95. resume,
  96. Resume(resumeStmt, resumeThreadId, resumeBreakInfo, resumeSpan,
  97. resumeHistory, resumeHistoryIx),
  98. History(historyBreakInfo, historyEnclosingDecls),
  99. GHC.getHistorySpan, getHistoryModule,
  100. getResumeContext,
  101. abandon, abandonAll,
  102. InteractiveEval.back,
  103. InteractiveEval.forward,
  104. showModule,
  105. isModuleInterpreted,
  106. InteractiveEval.compileExpr, HValue, dynCompileExpr,
  107. GHC.obtainTermFromId, GHC.obtainTermFromVal, reconstructType,
  108. modInfoModBreaks,
  109. ModBreaks(..), BreakIndex,
  110. BreakInfo(breakInfo_number, breakInfo_module),
  111. BreakArray, setBreakOn, setBreakOff, getBreak,
  112. #endif
  113. lookupName,
  114. #ifdef GHCI
  115. -- ** EXPERIMENTAL
  116. setGHCiMonad,
  117. #endif
  118. -- * Abstract syntax elements
  119. -- ** Packages
  120. PackageId,
  121. -- ** Modules
  122. Module, mkModule, pprModule, moduleName, modulePackageId,
  123. ModuleName, mkModuleName, moduleNameString,
  124. -- ** Names
  125. Name,
  126. isExternalName, nameModule, pprParenSymName, nameSrcSpan,
  127. NamedThing(..),
  128. RdrName(Qual,Unqual),
  129. -- ** Identifiers
  130. Id, idType,
  131. isImplicitId, isDeadBinder,
  132. isExportedId, isLocalId, isGlobalId,
  133. isRecordSelector,
  134. isPrimOpId, isFCallId, isClassOpId_maybe,
  135. isDataConWorkId, idDataCon,
  136. isBottomingId, isDictonaryId,
  137. recordSelectorFieldLabel,
  138. -- ** Type constructors
  139. TyCon,
  140. tyConTyVars, tyConDataCons, tyConArity,
  141. isClassTyCon, isSynTyCon, isNewTyCon, isPrimTyCon, isFunTyCon,
  142. isFamilyTyCon, tyConClass_maybe,
  143. synTyConRhs_maybe, synTyConDefn_maybe, synTyConResKind,
  144. -- ** Type variables
  145. TyVar,
  146. alphaTyVars,
  147. -- ** Data constructors
  148. DataCon,
  149. dataConSig, dataConType, dataConTyCon, dataConFieldLabels,
  150. dataConIsInfix, isVanillaDataCon, dataConUserType,
  151. dataConStrictMarks,
  152. StrictnessMark(..), isMarkedStrict,
  153. -- ** Classes
  154. Class,
  155. classMethods, classSCTheta, classTvsFds, classATs,
  156. pprFundeps,
  157. -- ** Instances
  158. ClsInst,
  159. instanceDFunId,
  160. pprInstance, pprInstanceHdr,
  161. pprFamInst,
  162. FamInst, Branched,
  163. -- ** Types and Kinds
  164. Type, splitForAllTys, funResultTy,
  165. pprParendType, pprTypeApp,
  166. Kind,
  167. PredType,
  168. ThetaType, pprForAll, pprThetaArrowTy,
  169. -- ** Entities
  170. TyThing(..),
  171. -- ** Syntax
  172. module HsSyn, -- ToDo: remove extraneous bits
  173. -- ** Fixities
  174. FixityDirection(..),
  175. defaultFixity, maxPrecedence,
  176. negateFixity,
  177. compareFixity,
  178. -- ** Source locations
  179. SrcLoc(..), RealSrcLoc,
  180. mkSrcLoc, noSrcLoc,
  181. srcLocFile, srcLocLine, srcLocCol,
  182. SrcSpan(..), RealSrcSpan,
  183. mkSrcSpan, srcLocSpan, isGoodSrcSpan, noSrcSpan,
  184. srcSpanStart, srcSpanEnd,
  185. srcSpanFile,
  186. srcSpanStartLine, srcSpanEndLine,
  187. srcSpanStartCol, srcSpanEndCol,
  188. -- ** Located
  189. GenLocated(..), Located,
  190. -- *** Constructing Located
  191. noLoc, mkGeneralLocated,
  192. -- *** Deconstructing Located
  193. getLoc, unLoc,
  194. -- *** Combining and comparing Located values
  195. eqLocated, cmpLocated, combineLocs, addCLoc,
  196. leftmost_smallest, leftmost_largest, rightmost,
  197. spans, isSubspanOf,
  198. -- * Exceptions
  199. GhcException(..), showGhcException,
  200. -- * Token stream manipulations
  201. Token,
  202. getTokenStream, getRichTokenStream,
  203. showRichTokenStream, addSourceToTokens,
  204. -- * Pure interface to the parser
  205. parser,
  206. -- * Miscellaneous
  207. --sessionHscEnv,
  208. cyclicModuleErr,
  209. ) where
  210. {-
  211. ToDo:
  212. * inline bits of HscMain here to simplify layering: hscTcExpr, hscStmt.
  213. * what StaticFlags should we expose, if any?
  214. -}
  215. #include "HsVersions.h"
  216. #ifdef GHCI
  217. import Linker ( HValue )
  218. import ByteCodeInstr
  219. import BreakArray
  220. import InteractiveEval
  221. #endif
  222. import HscMain
  223. import GhcMake
  224. import DriverPipeline ( compileOne' )
  225. import GhcMonad
  226. import TcRnMonad ( finalSafeMode )
  227. import TcRnTypes
  228. import Packages
  229. import NameSet
  230. import RdrName
  231. import qualified HsSyn -- hack as we want to reexport the whole module
  232. import HsSyn
  233. import Type hiding( typeKind )
  234. import Kind ( synTyConResKind )
  235. import TcType hiding( typeKind )
  236. import Id
  237. import TysPrim ( alphaTyVars )
  238. import TyCon
  239. import Class
  240. import DataCon
  241. import Name hiding ( varName )
  242. import Avail
  243. import InstEnv
  244. import FamInstEnv
  245. import SrcLoc
  246. import CoreSyn
  247. import TidyPgm
  248. import DriverPhases ( Phase(..), isHaskellSrcFilename )
  249. import Finder
  250. import HscTypes
  251. import DynFlags
  252. import StaticFlags
  253. import SysTools
  254. import Annotations
  255. import Module
  256. import UniqFM
  257. import Panic
  258. import Bag ( unitBag )
  259. import ErrUtils
  260. import MonadUtils
  261. import Util
  262. import StringBuffer
  263. import Outputable
  264. import BasicTypes
  265. import Maybes ( expectJust )
  266. import FastString
  267. import qualified Parser
  268. import Lexer
  269. import System.Directory ( doesFileExist, getCurrentDirectory )
  270. import Data.Maybe
  271. import Data.List ( find )
  272. import Data.Time
  273. import Data.Typeable ( Typeable )
  274. import Data.Word ( Word8 )
  275. import Control.Monad
  276. import System.Exit ( exitWith, ExitCode(..) )
  277. import Exception
  278. import Data.IORef
  279. import System.FilePath
  280. import System.IO
  281. import Prelude hiding (init)
  282. -- %************************************************************************
  283. -- %* *
  284. -- Initialisation: exception handlers
  285. -- %* *
  286. -- %************************************************************************
  287. -- | Install some default exception handlers and run the inner computation.
  288. -- Unless you want to handle exceptions yourself, you should wrap this around
  289. -- the top level of your program. The default handlers output the error
  290. -- message(s) to stderr and exit cleanly.
  291. defaultErrorHandler :: (ExceptionMonad m, MonadIO m)
  292. => FatalMessager -> FlushOut -> m a -> m a
  293. defaultErrorHandler fm (FlushOut flushOut) inner =
  294. -- top-level exception handler: any unrecognised exception is a compiler bug.
  295. ghandle (\exception -> liftIO $ do
  296. flushOut
  297. case fromException exception of
  298. -- an IO exception probably isn't our fault, so don't panic
  299. Just (ioe :: IOException) ->
  300. fatalErrorMsg'' fm (show ioe)
  301. _ -> case fromException exception of
  302. Just UserInterrupt -> exitWith (ExitFailure 1)
  303. Just StackOverflow ->
  304. fatalErrorMsg'' fm "stack overflow: use +RTS -K<size> to increase it"
  305. _ -> case fromException exception of
  306. Just (ex :: ExitCode) -> liftIO $ throwIO ex
  307. _ ->
  308. fatalErrorMsg'' fm
  309. (show (Panic (show exception)))
  310. exitWith (ExitFailure 1)
  311. ) $
  312. -- error messages propagated as exceptions
  313. handleGhcException
  314. (\ge -> liftIO $ do
  315. flushOut
  316. case ge of
  317. PhaseFailed _ code -> exitWith code
  318. Signal _ -> exitWith (ExitFailure 1)
  319. _ -> do fatalErrorMsg'' fm (show ge)
  320. exitWith (ExitFailure 1)
  321. ) $
  322. inner
  323. -- | Install a default cleanup handler to remove temporary files deposited by
  324. -- a GHC run. This is separate from 'defaultErrorHandler', because you might
  325. -- want to override the error handling, but still get the ordinary cleanup
  326. -- behaviour.
  327. defaultCleanupHandler :: (ExceptionMonad m, MonadIO m) =>
  328. DynFlags -> m a -> m a
  329. defaultCleanupHandler dflags inner =
  330. -- make sure we clean up after ourselves
  331. inner `gfinally`
  332. (liftIO $ do
  333. cleanTempFiles dflags
  334. cleanTempDirs dflags
  335. )
  336. -- exceptions will be blocked while we clean the temporary files,
  337. -- so there shouldn't be any difficulty if we receive further
  338. -- signals.
  339. -- %************************************************************************
  340. -- %* *
  341. -- The Ghc Monad
  342. -- %* *
  343. -- %************************************************************************
  344. -- | Run function for the 'Ghc' monad.
  345. --
  346. -- It initialises the GHC session and warnings via 'initGhcMonad'. Each call
  347. -- to this function will create a new session which should not be shared among
  348. -- several threads.
  349. --
  350. -- Any errors not handled inside the 'Ghc' action are propagated as IO
  351. -- exceptions.
  352. runGhc :: Maybe FilePath -- ^ See argument to 'initGhcMonad'.
  353. -> Ghc a -- ^ The action to perform.
  354. -> IO a
  355. runGhc mb_top_dir ghc = do
  356. ref <- newIORef (panic "empty session")
  357. let session = Session ref
  358. flip unGhc session $ do
  359. initGhcMonad mb_top_dir
  360. ghc
  361. -- XXX: unregister interrupt handlers here?
  362. -- | Run function for 'GhcT' monad transformer.
  363. --
  364. -- It initialises the GHC session and warnings via 'initGhcMonad'. Each call
  365. -- to this function will create a new session which should not be shared among
  366. -- several threads.
  367. runGhcT :: (ExceptionMonad m, Functor m, MonadIO m) =>
  368. Maybe FilePath -- ^ See argument to 'initGhcMonad'.
  369. -> GhcT m a -- ^ The action to perform.
  370. -> m a
  371. runGhcT mb_top_dir ghct = do
  372. ref <- liftIO $ newIORef (panic "empty session")
  373. let session = Session ref
  374. flip unGhcT session $ do
  375. initGhcMonad mb_top_dir
  376. ghct
  377. -- | Initialise a GHC session.
  378. --
  379. -- If you implement a custom 'GhcMonad' you must call this function in the
  380. -- monad run function. It will initialise the session variable and clear all
  381. -- warnings.
  382. --
  383. -- The first argument should point to the directory where GHC's library files
  384. -- reside. More precisely, this should be the output of @ghc --print-libdir@
  385. -- of the version of GHC the module using this API is compiled with. For
  386. -- portability, you should use the @ghc-paths@ package, available at
  387. -- <http://hackage.haskell.org/cgi-bin/hackage-scripts/package/ghc-paths>.
  388. initGhcMonad :: GhcMonad m => Maybe FilePath -> m ()
  389. initGhcMonad mb_top_dir = do
  390. -- catch ^C
  391. liftIO $ installSignalHandlers
  392. liftIO $ initStaticOpts
  393. mySettings <- liftIO $ initSysTools mb_top_dir
  394. dflags <- liftIO $ initDynFlags (defaultDynFlags mySettings)
  395. env <- liftIO $ newHscEnv dflags
  396. setSession env
  397. -- %************************************************************************
  398. -- %* *
  399. -- Flags & settings
  400. -- %* *
  401. -- %************************************************************************
  402. -- $DynFlags
  403. --
  404. -- The GHC session maintains two sets of 'DynFlags':
  405. --
  406. -- * The "interactive" @DynFlags@, which are used for everything
  407. -- related to interactive evaluation, including 'runStmt',
  408. -- 'runDecls', 'exprType', 'lookupName' and so on (everything
  409. -- under \"Interactive evaluation\" in this module).
  410. --
  411. -- * The "program" @DynFlags@, which are used when loading
  412. -- whole modules with 'load'
  413. --
  414. -- 'setInteractiveDynFlags', 'getInteractiveDynFlags' work with the
  415. -- interactive @DynFlags@.
  416. --
  417. -- 'setProgramDynFlags', 'getProgramDynFlags' work with the
  418. -- program @DynFlags@.
  419. --
  420. -- 'setSessionDynFlags' sets both @DynFlags@, and 'getSessionDynFlags'
  421. -- retrieves the program @DynFlags@ (for backwards compatibility).
  422. -- | Updates both the interactive and program DynFlags in a Session.
  423. -- This also reads the package database (unless it has already been
  424. -- read), and prepares the compilers knowledge about packages. It can
  425. -- be called again to load new packages: just add new package flags to
  426. -- (packageFlags dflags).
  427. --
  428. -- Returns a list of new packages that may need to be linked in using
  429. -- the dynamic linker (see 'linkPackages') as a result of new package
  430. -- flags. If you are not doing linking or doing static linking, you
  431. -- can ignore the list of packages returned.
  432. --
  433. setSessionDynFlags :: GhcMonad m => DynFlags -> m [PackageId]
  434. setSessionDynFlags dflags = do
  435. (dflags', preload) <- liftIO $ initPackages dflags
  436. modifySession $ \h -> h{ hsc_dflags = dflags'
  437. , hsc_IC = (hsc_IC h){ ic_dflags = dflags' } }
  438. invalidateModSummaryCache
  439. return preload
  440. -- | Sets the program 'DynFlags'.
  441. setProgramDynFlags :: GhcMonad m => DynFlags -> m [PackageId]
  442. setProgramDynFlags dflags = do
  443. (dflags', preload) <- liftIO $ initPackages dflags
  444. modifySession $ \h -> h{ hsc_dflags = dflags' }
  445. invalidateModSummaryCache
  446. return preload
  447. -- When changing the DynFlags, we want the changes to apply to future
  448. -- loads, but without completely discarding the program. But the
  449. -- DynFlags are cached in each ModSummary in the hsc_mod_graph, so
  450. -- after a change to DynFlags, the changes would apply to new modules
  451. -- but not existing modules; this seems undesirable.
  452. --
  453. -- Furthermore, the GHC API client might expect that changing
  454. -- log_action would affect future compilation messages, but for those
  455. -- modules we have cached ModSummaries for, we'll continue to use the
  456. -- old log_action. This is definitely wrong (#7478).
  457. --
  458. -- Hence, we invalidate the ModSummary cache after changing the
  459. -- DynFlags. We do this by tweaking the date on each ModSummary, so
  460. -- that the next downsweep will think that all the files have changed
  461. -- and preprocess them again. This won't necessarily cause everything
  462. -- to be recompiled, because by the time we check whether we need to
  463. -- recopmile a module, we'll have re-summarised the module and have a
  464. -- correct ModSummary.
  465. --
  466. invalidateModSummaryCache :: GhcMonad m => m ()
  467. invalidateModSummaryCache =
  468. modifySession $ \h -> h { hsc_mod_graph = map inval (hsc_mod_graph h) }
  469. where
  470. inval ms = ms { ms_hs_date = addUTCTime (-1) (ms_hs_date ms) }
  471. -- | Returns the program 'DynFlags'.
  472. getProgramDynFlags :: GhcMonad m => m DynFlags
  473. getProgramDynFlags = getSessionDynFlags
  474. -- | Set the 'DynFlags' used to evaluate interactive expressions.
  475. -- Note: this cannot be used for changes to packages. Use
  476. -- 'setSessionDynFlags', or 'setProgramDynFlags' and then copy the
  477. -- 'pkgState' into the interactive @DynFlags@.
  478. setInteractiveDynFlags :: GhcMonad m => DynFlags -> m ()
  479. setInteractiveDynFlags dflags = do
  480. modifySession $ \h -> h{ hsc_IC = (hsc_IC h) { ic_dflags = dflags }}
  481. -- | Get the 'DynFlags' used to evaluate interactive expressions.
  482. getInteractiveDynFlags :: GhcMonad m => m DynFlags
  483. getInteractiveDynFlags = withSession $ \h -> return (ic_dflags (hsc_IC h))
  484. parseDynamicFlags :: MonadIO m =>
  485. DynFlags -> [Located String]
  486. -> m (DynFlags, [Located String], [Located String])
  487. parseDynamicFlags = parseDynamicFlagsCmdLine
  488. -- %************************************************************************
  489. -- %* *
  490. -- Setting, getting, and modifying the targets
  491. -- %* *
  492. -- %************************************************************************
  493. -- ToDo: think about relative vs. absolute file paths. And what
  494. -- happens when the current directory changes.
  495. -- | Sets the targets for this session. Each target may be a module name
  496. -- or a filename. The targets correspond to the set of root modules for
  497. -- the program\/library. Unloading the current program is achieved by
  498. -- setting the current set of targets to be empty, followed by 'load'.
  499. setTargets :: GhcMonad m => [Target] -> m ()
  500. setTargets targets = modifySession (\h -> h{ hsc_targets = targets })
  501. -- | Returns the current set of targets
  502. getTargets :: GhcMonad m => m [Target]
  503. getTargets = withSession (return . hsc_targets)
  504. -- | Add another target.
  505. addTarget :: GhcMonad m => Target -> m ()
  506. addTarget target
  507. = modifySession (\h -> h{ hsc_targets = target : hsc_targets h })
  508. -- | Remove a target
  509. removeTarget :: GhcMonad m => TargetId -> m ()
  510. removeTarget target_id
  511. = modifySession (\h -> h{ hsc_targets = filter (hsc_targets h) })
  512. where
  513. filter targets = [ t | t@(Target id _ _) <- targets, id /= target_id ]
  514. -- | Attempts to guess what Target a string refers to. This function
  515. -- implements the @--make@/GHCi command-line syntax for filenames:
  516. --
  517. -- - if the string looks like a Haskell source filename, then interpret it
  518. -- as such
  519. --
  520. -- - if adding a .hs or .lhs suffix yields the name of an existing file,
  521. -- then use that
  522. --
  523. -- - otherwise interpret the string as a module name
  524. --
  525. guessTarget :: GhcMonad m => String -> Maybe Phase -> m Target
  526. guessTarget str (Just phase)
  527. = return (Target (TargetFile str (Just phase)) True Nothing)
  528. guessTarget str Nothing
  529. | isHaskellSrcFilename file
  530. = return (target (TargetFile file Nothing))
  531. | otherwise
  532. = do exists <- liftIO $ doesFileExist hs_file
  533. if exists
  534. then return (target (TargetFile hs_file Nothing))
  535. else do
  536. exists <- liftIO $ doesFileExist lhs_file
  537. if exists
  538. then return (target (TargetFile lhs_file Nothing))
  539. else do
  540. if looksLikeModuleName file
  541. then return (target (TargetModule (mkModuleName file)))
  542. else do
  543. dflags <- getDynFlags
  544. liftIO $ throwGhcExceptionIO
  545. (ProgramError (showSDoc dflags $
  546. text "target" <+> quotes (text file) <+>
  547. text "is not a module name or a source file"))
  548. where
  549. (file,obj_allowed)
  550. | '*':rest <- str = (rest, False)
  551. | otherwise = (str, True)
  552. hs_file = file <.> "hs"
  553. lhs_file = file <.> "lhs"
  554. target tid = Target tid obj_allowed Nothing
  555. -- | Inform GHC that the working directory has changed. GHC will flush
  556. -- its cache of module locations, since it may no longer be valid.
  557. --
  558. -- Note: Before changing the working directory make sure all threads running
  559. -- in the same session have stopped. If you change the working directory,
  560. -- you should also unload the current program (set targets to empty,
  561. -- followed by load).
  562. workingDirectoryChanged :: GhcMonad m => m ()
  563. workingDirectoryChanged = withSession $ (liftIO . flushFinderCaches)
  564. -- %************************************************************************
  565. -- %* *
  566. -- Running phases one at a time
  567. -- %* *
  568. -- %************************************************************************
  569. class ParsedMod m where
  570. modSummary :: m -> ModSummary
  571. parsedSource :: m -> ParsedSource
  572. class ParsedMod m => TypecheckedMod m where
  573. renamedSource :: m -> Maybe RenamedSource
  574. typecheckedSource :: m -> TypecheckedSource
  575. moduleInfo :: m -> ModuleInfo
  576. tm_internals :: m -> (TcGblEnv, ModDetails)
  577. -- ToDo: improvements that could be made here:
  578. -- if the module succeeded renaming but not typechecking,
  579. -- we can still get back the GlobalRdrEnv and exports, so
  580. -- perhaps the ModuleInfo should be split up into separate
  581. -- fields.
  582. class TypecheckedMod m => DesugaredMod m where
  583. coreModule :: m -> ModGuts
  584. -- | The result of successful parsing.
  585. data ParsedModule =
  586. ParsedModule { pm_mod_summary :: ModSummary
  587. , pm_parsed_source :: ParsedSource
  588. , pm_extra_src_files :: [FilePath] }
  589. instance ParsedMod ParsedModule where
  590. modSummary m = pm_mod_summary m
  591. parsedSource m = pm_parsed_source m
  592. -- | The result of successful typechecking. It also contains the parser
  593. -- result.
  594. data TypecheckedModule =
  595. TypecheckedModule { tm_parsed_module :: ParsedModule
  596. , tm_renamed_source :: Maybe RenamedSource
  597. , tm_typechecked_source :: TypecheckedSource
  598. , tm_checked_module_info :: ModuleInfo
  599. , tm_internals_ :: (TcGblEnv, ModDetails)
  600. }
  601. instance ParsedMod TypecheckedModule where
  602. modSummary m = modSummary (tm_parsed_module m)
  603. parsedSource m = parsedSource (tm_parsed_module m)
  604. instance TypecheckedMod TypecheckedModule where
  605. renamedSource m = tm_renamed_source m
  606. typecheckedSource m = tm_typechecked_source m
  607. moduleInfo m = tm_checked_module_info m
  608. tm_internals m = tm_internals_ m
  609. -- | The result of successful desugaring (i.e., translation to core). Also
  610. -- contains all the information of a typechecked module.
  611. data DesugaredModule =
  612. DesugaredModule { dm_typechecked_module :: TypecheckedModule
  613. , dm_core_module :: ModGuts
  614. }
  615. instance ParsedMod DesugaredModule where
  616. modSummary m = modSummary (dm_typechecked_module m)
  617. parsedSource m = parsedSource (dm_typechecked_module m)
  618. instance TypecheckedMod DesugaredModule where
  619. renamedSource m = renamedSource (dm_typechecked_module m)
  620. typecheckedSource m = typecheckedSource (dm_typechecked_module m)
  621. moduleInfo m = moduleInfo (dm_typechecked_module m)
  622. tm_internals m = tm_internals_ (dm_typechecked_module m)
  623. instance DesugaredMod DesugaredModule where
  624. coreModule m = dm_core_module m
  625. type ParsedSource = Located (HsModule RdrName)
  626. type RenamedSource = (HsGroup Name, [LImportDecl Name], Maybe [LIE Name],
  627. Maybe LHsDocString)
  628. type TypecheckedSource = LHsBinds Id
  629. -- NOTE:
  630. -- - things that aren't in the output of the typechecker right now:
  631. -- - the export list
  632. -- - the imports
  633. -- - type signatures
  634. -- - type/data/newtype declarations
  635. -- - class declarations
  636. -- - instances
  637. -- - extra things in the typechecker's output:
  638. -- - default methods are turned into top-level decls.
  639. -- - dictionary bindings
  640. -- | Return the 'ModSummary' of a module with the given name.
  641. --
  642. -- The module must be part of the module graph (see 'hsc_mod_graph' and
  643. -- 'ModuleGraph'). If this is not the case, this function will throw a
  644. -- 'GhcApiError'.
  645. --
  646. -- This function ignores boot modules and requires that there is only one
  647. -- non-boot module with the given name.
  648. getModSummary :: GhcMonad m => ModuleName -> m ModSummary
  649. getModSummary mod = do
  650. mg <- liftM hsc_mod_graph getSession
  651. case [ ms | ms <- mg, ms_mod_name ms == mod, not (isBootSummary ms) ] of
  652. [] -> do dflags <- getDynFlags
  653. liftIO $ throwIO $ mkApiErr dflags (text "Module not part of module graph")
  654. [ms] -> return ms
  655. multiple -> do dflags <- getDynFlags
  656. liftIO $ throwIO $ mkApiErr dflags (text "getModSummary is ambiguous: " <+> ppr multiple)
  657. -- | Parse a module.
  658. --
  659. -- Throws a 'SourceError' on parse error.
  660. parseModule :: GhcMonad m => ModSummary -> m ParsedModule
  661. parseModule ms = do
  662. hsc_env <- getSession
  663. let hsc_env_tmp = hsc_env { hsc_dflags = ms_hspp_opts ms }
  664. hpm <- liftIO $ hscParse hsc_env_tmp ms
  665. return (ParsedModule ms (hpm_module hpm) (hpm_src_files hpm))
  666. -- | Typecheck and rename a parsed module.
  667. --
  668. -- Throws a 'SourceError' if either fails.
  669. typecheckModule :: GhcMonad m => ParsedModule -> m TypecheckedModule
  670. typecheckModule pmod = do
  671. let ms = modSummary pmod
  672. hsc_env <- getSession
  673. let hsc_env_tmp = hsc_env { hsc_dflags = ms_hspp_opts ms }
  674. (tc_gbl_env, rn_info)
  675. <- liftIO $ hscTypecheckRename hsc_env_tmp ms $
  676. HsParsedModule { hpm_module = parsedSource pmod,
  677. hpm_src_files = pm_extra_src_files pmod }
  678. details <- liftIO $ makeSimpleDetails hsc_env_tmp tc_gbl_env
  679. safe <- liftIO $ finalSafeMode (ms_hspp_opts ms) tc_gbl_env
  680. return $
  681. TypecheckedModule {
  682. tm_internals_ = (tc_gbl_env, details),
  683. tm_parsed_module = pmod,
  684. tm_renamed_source = rn_info,
  685. tm_typechecked_source = tcg_binds tc_gbl_env,
  686. tm_checked_module_info =
  687. ModuleInfo {
  688. minf_type_env = md_types details,
  689. minf_exports = availsToNameSet $ md_exports details,
  690. minf_rdr_env = Just (tcg_rdr_env tc_gbl_env),
  691. minf_instances = md_insts details,
  692. minf_iface = Nothing,
  693. minf_safe = safe
  694. #ifdef GHCI
  695. ,minf_modBreaks = emptyModBreaks
  696. #endif
  697. }}
  698. -- | Desugar a typechecked module.
  699. desugarModule :: GhcMonad m => TypecheckedModule -> m DesugaredModule
  700. desugarModule tcm = do
  701. let ms = modSummary tcm
  702. let (tcg, _) = tm_internals tcm
  703. hsc_env <- getSession
  704. let hsc_env_tmp = hsc_env { hsc_dflags = ms_hspp_opts ms }
  705. guts <- liftIO $ hscDesugar hsc_env_tmp ms tcg
  706. return $
  707. DesugaredModule {
  708. dm_typechecked_module = tcm,
  709. dm_core_module = guts
  710. }
  711. -- | Load a module. Input doesn't need to be desugared.
  712. --
  713. -- A module must be loaded before dependent modules can be typechecked. This
  714. -- always includes generating a 'ModIface' and, depending on the
  715. -- 'DynFlags.hscTarget', may also include code generation.
  716. --
  717. -- This function will always cause recompilation and will always overwrite
  718. -- previous compilation results (potentially files on disk).
  719. --
  720. loadModule :: (TypecheckedMod mod, GhcMonad m) => mod -> m mod
  721. loadModule tcm = do
  722. let ms = modSummary tcm
  723. let mod = ms_mod_name ms
  724. let loc = ms_location ms
  725. let (tcg, _details) = tm_internals tcm
  726. mb_linkable <- case ms_obj_date ms of
  727. Just t | t > ms_hs_date ms -> do
  728. l <- liftIO $ findObjectLinkable (ms_mod ms)
  729. (ml_obj_file loc) t
  730. return (Just l)
  731. _otherwise -> return Nothing
  732. let source_modified | isNothing mb_linkable = SourceModified
  733. | otherwise = SourceUnmodified
  734. -- we can't determine stability here
  735. -- compile doesn't change the session
  736. hsc_env <- getSession
  737. mod_info <- liftIO $ compileOne' (Just tcg) Nothing
  738. hsc_env ms 1 1 Nothing mb_linkable
  739. source_modified
  740. modifySession $ \e -> e{ hsc_HPT = addToUFM (hsc_HPT e) mod mod_info }
  741. return tcm
  742. -- %************************************************************************
  743. -- %* *
  744. -- Dealing with Core
  745. -- %* *
  746. -- %************************************************************************
  747. -- | A CoreModule consists of just the fields of a 'ModGuts' that are needed for
  748. -- the 'GHC.compileToCoreModule' interface.
  749. data CoreModule
  750. = CoreModule {
  751. -- | Module name
  752. cm_module :: !Module,
  753. -- | Type environment for types declared in this module
  754. cm_types :: !TypeEnv,
  755. -- | Declarations
  756. cm_binds :: CoreProgram,
  757. -- | Safe Haskell mode
  758. cm_safe :: SafeHaskellMode
  759. }
  760. instance Outputable CoreModule where
  761. ppr (CoreModule {cm_module = mn, cm_types = te, cm_binds = cb,
  762. cm_safe = sf})
  763. = text "%module" <+> ppr mn <+> parens (ppr sf) <+> ppr te
  764. $$ vcat (map ppr cb)
  765. -- | This is the way to get access to the Core bindings corresponding
  766. -- to a module. 'compileToCore' parses, typechecks, and
  767. -- desugars the module, then returns the resulting Core module (consisting of
  768. -- the module name, type declarations, and function declarations) if
  769. -- successful.
  770. compileToCoreModule :: GhcMonad m => FilePath -> m CoreModule
  771. compileToCoreModule = compileCore False
  772. -- | Like compileToCoreModule, but invokes the simplifier, so
  773. -- as to return simplified and tidied Core.
  774. compileToCoreSimplified :: GhcMonad m => FilePath -> m CoreModule
  775. compileToCoreSimplified = compileCore True
  776. -- | Takes a CoreModule and compiles the bindings therein
  777. -- to object code. The first argument is a bool flag indicating
  778. -- whether to run the simplifier.
  779. -- The resulting .o, .hi, and executable files, if any, are stored in the
  780. -- current directory, and named according to the module name.
  781. -- This has only so far been tested with a single self-contained module.
  782. compileCoreToObj :: GhcMonad m
  783. => Bool -> CoreModule -> FilePath -> FilePath -> m ()
  784. compileCoreToObj simplify cm@(CoreModule{ cm_module = mName })
  785. output_fn extCore_filename = do
  786. dflags <- getSessionDynFlags
  787. currentTime <- liftIO $ getCurrentTime
  788. cwd <- liftIO $ getCurrentDirectory
  789. modLocation <- liftIO $ mkHiOnlyModLocation dflags (hiSuf dflags) cwd
  790. ((moduleNameSlashes . moduleName) mName)
  791. let modSum = ModSummary { ms_mod = mName,
  792. ms_hsc_src = ExtCoreFile,
  793. ms_location = modLocation,
  794. -- By setting the object file timestamp to Nothing,
  795. -- we always force recompilation, which is what we
  796. -- want. (Thus it doesn't matter what the timestamp
  797. -- for the (nonexistent) source file is.)
  798. ms_hs_date = currentTime,
  799. ms_obj_date = Nothing,
  800. -- Only handling the single-module case for now, so no imports.
  801. ms_srcimps = [],
  802. ms_textual_imps = [],
  803. -- No source file
  804. ms_hspp_file = "",
  805. ms_hspp_opts = dflags,
  806. ms_hspp_buf = Nothing
  807. }
  808. hsc_env <- getSession
  809. liftIO $ hscCompileCore hsc_env simplify (cm_safe cm) modSum (cm_binds cm) output_fn extCore_filename
  810. compileCore :: GhcMonad m => Bool -> FilePath -> m CoreModule
  811. compileCore simplify fn = do
  812. -- First, set the target to the desired filename
  813. target <- guessTarget fn Nothing
  814. addTarget target
  815. _ <- load LoadAllTargets
  816. -- Then find dependencies
  817. modGraph <- depanal [] True
  818. case find ((== fn) . msHsFilePath) modGraph of
  819. Just modSummary -> do
  820. -- Now we have the module name;
  821. -- parse, typecheck and desugar the module
  822. mod_guts <- coreModule `fmap`
  823. -- TODO: space leaky: call hsc* directly?
  824. (desugarModule =<< typecheckModule =<< parseModule modSummary)
  825. liftM (gutsToCoreModule (mg_safe_haskell mod_guts)) $
  826. if simplify
  827. then do
  828. -- If simplify is true: simplify (hscSimplify), then tidy
  829. -- (tidyProgram).
  830. hsc_env <- getSession
  831. simpl_guts <- liftIO $ hscSimplify hsc_env mod_guts
  832. tidy_guts <- liftIO $ tidyProgram hsc_env simpl_guts
  833. return $ Left tidy_guts
  834. else
  835. return $ Right mod_guts
  836. Nothing -> panic "compileToCoreModule: target FilePath not found in\
  837. module dependency graph"
  838. where -- two versions, based on whether we simplify (thus run tidyProgram,
  839. -- which returns a (CgGuts, ModDetails) pair, or not (in which case
  840. -- we just have a ModGuts.
  841. gutsToCoreModule :: SafeHaskellMode
  842. -> Either (CgGuts, ModDetails) ModGuts
  843. -> CoreModule
  844. gutsToCoreModule safe_mode (Left (cg, md)) = CoreModule {
  845. cm_module = cg_module cg,
  846. cm_types = md_types md,
  847. cm_binds = cg_binds cg,
  848. cm_safe = safe_mode
  849. }
  850. gutsToCoreModule safe_mode (Right mg) = CoreModule {
  851. cm_module = mg_module mg,
  852. cm_types = typeEnvFromEntities (bindersOfBinds (mg_binds mg))
  853. (mg_tcs mg)
  854. (mg_fam_insts mg),
  855. cm_binds = mg_binds mg,
  856. cm_safe = safe_mode
  857. }
  858. -- %************************************************************************
  859. -- %* *
  860. -- Inspecting the session
  861. -- %* *
  862. -- %************************************************************************
  863. -- | Get the module dependency graph.
  864. getModuleGraph :: GhcMonad m => m ModuleGraph -- ToDo: DiGraph ModSummary
  865. getModuleGraph = liftM hsc_mod_graph getSession
  866. -- | Determines whether a set of modules requires Template Haskell.
  867. --
  868. -- Note that if the session's 'DynFlags' enabled Template Haskell when
  869. -- 'depanal' was called, then each module in the returned module graph will
  870. -- have Template Haskell enabled whether it is actually needed or not.
  871. needsTemplateHaskell :: ModuleGraph -> Bool
  872. needsTemplateHaskell ms =
  873. any (xopt Opt_TemplateHaskell . ms_hspp_opts) ms
  874. -- | Return @True@ <==> module is loaded.
  875. isLoaded :: GhcMonad m => ModuleName -> m Bool
  876. isLoaded m = withSession $ \hsc_env ->
  877. return $! isJust (lookupUFM (hsc_HPT hsc_env) m)
  878. -- | Return the bindings for the current interactive session.
  879. getBindings :: GhcMonad m => m [TyThing]
  880. getBindings = withSession $ \hsc_env ->
  881. return $ icInScopeTTs $ hsc_IC hsc_env
  882. -- | Return the instances for the current interactive session.
  883. getInsts :: GhcMonad m => m ([ClsInst], [FamInst Branched])
  884. getInsts = withSession $ \hsc_env ->
  885. return $ ic_instances (hsc_IC hsc_env)
  886. getPrintUnqual :: GhcMonad m => m PrintUnqualified
  887. getPrintUnqual = withSession $ \hsc_env ->
  888. return (icPrintUnqual (hsc_dflags hsc_env) (hsc_IC hsc_env))
  889. -- | Container for information about a 'Module'.
  890. data ModuleInfo = ModuleInfo {
  891. minf_type_env :: TypeEnv,
  892. minf_exports :: NameSet, -- ToDo, [AvailInfo] like ModDetails?
  893. minf_rdr_env :: Maybe GlobalRdrEnv, -- Nothing for a compiled/package mod
  894. minf_instances :: [ClsInst],
  895. minf_iface :: Maybe ModIface,
  896. minf_safe :: SafeHaskellMode
  897. #ifdef GHCI
  898. ,minf_modBreaks :: ModBreaks
  899. #endif
  900. }
  901. -- We don't want HomeModInfo here, because a ModuleInfo applies
  902. -- to package modules too.
  903. -- | Request information about a loaded 'Module'
  904. getModuleInfo :: GhcMonad m => Module -> m (Maybe ModuleInfo) -- XXX: Maybe X
  905. getModuleInfo mdl = withSession $ \hsc_env -> do
  906. let mg = hsc_mod_graph hsc_env
  907. if mdl `elem` map ms_mod mg
  908. then liftIO $ getHomeModuleInfo hsc_env mdl
  909. else do
  910. {- if isHomeModule (hsc_dflags hsc_env) mdl
  911. then return Nothing
  912. else -} liftIO $ getPackageModuleInfo hsc_env mdl
  913. -- ToDo: we don't understand what the following comment means.
  914. -- (SDM, 19/7/2011)
  915. -- getPackageModuleInfo will attempt to find the interface, so
  916. -- we don't want to call it for a home module, just in case there
  917. -- was a problem loading the module and the interface doesn't
  918. -- exist... hence the isHomeModule test here. (ToDo: reinstate)
  919. getPackageModuleInfo :: HscEnv -> Module -> IO (Maybe ModuleInfo)
  920. #ifdef GHCI
  921. getPackageModuleInfo hsc_env mdl
  922. = do eps <- hscEPS hsc_env
  923. iface <- hscGetModuleInterface hsc_env mdl
  924. let
  925. avails = mi_exports iface
  926. names = availsToNameSet avails
  927. pte = eps_PTE eps
  928. tys = [ ty | name <- concatMap availNames avails,
  929. Just ty <- [lookupTypeEnv pte name] ]
  930. --
  931. return (Just (ModuleInfo {
  932. minf_type_env = mkTypeEnv tys,
  933. minf_exports = names,
  934. minf_rdr_env = Just $! availsToGlobalRdrEnv (moduleName mdl) avails,
  935. minf_instances = error "getModuleInfo: instances for package module unimplemented",
  936. minf_iface = Just iface,
  937. minf_safe = getSafeMode $ mi_trust iface,
  938. minf_modBreaks = emptyModBreaks
  939. }))
  940. #else
  941. -- bogusly different for non-GHCI (ToDo)
  942. getPackageModuleInfo _hsc_env _mdl = do
  943. return Nothing
  944. #endif
  945. getHomeModuleInfo :: HscEnv -> Module -> IO (Maybe ModuleInfo)
  946. getHomeModuleInfo hsc_env mdl =
  947. case lookupUFM (hsc_HPT hsc_env) (moduleName mdl) of
  948. Nothing -> return Nothing
  949. Just hmi -> do
  950. let details = hm_details hmi
  951. iface = hm_iface hmi
  952. return (Just (ModuleInfo {
  953. minf_type_env = md_types details,
  954. minf_exports = availsToNameSet (md_exports details),
  955. minf_rdr_env = mi_globals $! hm_iface hmi,
  956. minf_instances = md_insts details,
  957. minf_iface = Just iface,
  958. minf_safe = getSafeMode $ mi_trust iface
  959. #ifdef GHCI
  960. ,minf_modBreaks = getModBreaks hmi
  961. #endif
  962. }))
  963. -- | The list of top-level entities defined in a module
  964. modInfoTyThings :: ModuleInfo -> [TyThing]
  965. modInfoTyThings minf = typeEnvElts (minf_type_env minf)
  966. modInfoTopLevelScope :: ModuleInfo -> Maybe [Name]
  967. modInfoTopLevelScope minf
  968. = fmap (map gre_name . globalRdrEnvElts) (minf_rdr_env minf)
  969. modInfoExports :: ModuleInfo -> [Name]
  970. modInfoExports minf = nameSetToList $! minf_exports minf
  971. -- | Returns the instances defined by the specified module.
  972. -- Warning: currently unimplemented for package modules.
  973. modInfoInstances :: ModuleInfo -> [ClsInst]
  974. modInfoInstances = minf_instances
  975. modInfoIsExportedName :: ModuleInfo -> Name -> Bool
  976. modInfoIsExportedName minf name = elemNameSet name (minf_exports minf)
  977. mkPrintUnqualifiedForModule :: GhcMonad m =>
  978. ModuleInfo
  979. -> m (Maybe PrintUnqualified) -- XXX: returns a Maybe X
  980. mkPrintUnqualifiedForModule minf = withSession $ \hsc_env -> do
  981. return (fmap (mkPrintUnqualified (hsc_dflags hsc_env)) (minf_rdr_env minf))
  982. modInfoLookupName :: GhcMonad m =>
  983. ModuleInfo -> Name
  984. -> m (Maybe TyThing) -- XXX: returns a Maybe X
  985. modInfoLookupName minf name = withSession $ \hsc_env -> do
  986. case lookupTypeEnv (minf_type_env minf) name of
  987. Just tyThing -> return (Just tyThing)
  988. Nothing -> do
  989. eps <- liftIO $ readIORef (hsc_EPS hsc_env)
  990. return $! lookupType (hsc_dflags hsc_env)
  991. (hsc_HPT hsc_env) (eps_PTE eps) name
  992. modInfoIface :: ModuleInfo -> Maybe ModIface
  993. modInfoIface = minf_iface
  994. -- | Retrieve module safe haskell mode
  995. modInfoSafe :: ModuleInfo -> SafeHaskellMode
  996. modInfoSafe = minf_safe
  997. #ifdef GHCI
  998. modInfoModBreaks :: ModuleInfo -> ModBreaks
  999. modInfoModBreaks = minf_modBreaks
  1000. #endif
  1001. isDictonaryId :: Id -> Bool
  1002. isDictonaryId id
  1003. = case tcSplitSigmaTy (idType id) of { (_tvs, _theta, tau) -> isDictTy tau }
  1004. -- | Looks up a global name: that is, any top-level name in any
  1005. -- visible module. Unlike 'lookupName', lookupGlobalName does not use
  1006. -- the interactive context, and therefore does not require a preceding
  1007. -- 'setContext'.
  1008. lookupGlobalName :: GhcMonad m => Name -> m (Maybe TyThing)
  1009. lookupGlobalName name = withSession $ \hsc_env -> do
  1010. liftIO $ lookupTypeHscEnv hsc_env name
  1011. findGlobalAnns :: (GhcMonad m, Typeable a) => ([Word8] -> a) -> AnnTarget Name -> m [a]
  1012. findGlobalAnns deserialize target = withSession $ \hsc_env -> do
  1013. ann_env <- liftIO $ prepareAnnotations hsc_env Nothing
  1014. return (findAnns deserialize ann_env target)
  1015. #ifdef GHCI
  1016. -- | get the GlobalRdrEnv for a session
  1017. getGRE :: GhcMonad m => m GlobalRdrEnv
  1018. getGRE = withSession $ \hsc_env-> return $ ic_rn_gbl_env (hsc_IC hsc_env)
  1019. #endif
  1020. -- -----------------------------------------------------------------------------
  1021. -- | Return all /external/ modules available in the package database.
  1022. -- Modules from the current session (i.e., from the 'HomePackageTable') are
  1023. -- not included.
  1024. packageDbModules :: GhcMonad m =>
  1025. Bool -- ^ Only consider exposed packages.
  1026. -> m [Module]
  1027. packageDbModules only_exposed = do
  1028. dflags <- getSessionDynFlags
  1029. let pkgs = eltsUFM (pkgIdMap (pkgState dflags))
  1030. return $
  1031. [ mkModule pid modname | p <- pkgs
  1032. , not only_exposed || exposed p
  1033. , let pid = packageConfigId p
  1034. , modname <- exposedModules p ]
  1035. -- -----------------------------------------------------------------------------
  1036. -- Misc exported utils
  1037. dataConType :: DataCon -> Type
  1038. dataConType dc = idType (dataConWrapId dc)
  1039. -- | print a 'NamedThing', adding parentheses if the name is an operator.
  1040. pprParenSymName :: NamedThing a => a -> SDoc
  1041. pprParenSymName a = parenSymOcc (getOccName a) (ppr (getName a))
  1042. -- ----------------------------------------------------------------------------
  1043. #if 0
  1044. -- ToDo:
  1045. -- - Data and Typeable instances for HsSyn.
  1046. -- ToDo: check for small transformations that happen to the syntax in
  1047. -- the typechecker (eg. -e ==> negate e, perhaps for fromIntegral)
  1048. -- ToDo: maybe use TH syntax instead of IfaceSyn? There's already a way
  1049. -- to get from TyCons, Ids etc. to TH syntax (reify).
  1050. -- :browse will use either lm_toplev or inspect lm_interface, depending
  1051. -- on whether the module is interpreted or not.
  1052. #endif
  1053. -- Extract the filename, stringbuffer content and dynflags associed to a module
  1054. --
  1055. -- XXX: Explain pre-conditions
  1056. getModuleSourceAndFlags :: GhcMonad m => Module -> m (String, StringBuffer, DynFlags)
  1057. getModuleSourceAndFlags mod = do
  1058. m <- getModSummary (moduleName mod)
  1059. case ml_hs_file $ ms_location m of
  1060. Nothing -> do dflags <- getDynFlags
  1061. liftIO $ throwIO $ mkApiErr dflags (text "No source available for module " <+> ppr mod)
  1062. Just sourceFile -> do
  1063. source <- liftIO $ hGetStringBuffer sourceFile
  1064. return (sourceFile, source, ms_hspp_opts m)
  1065. -- | Return module source as token stream, including comments.
  1066. --
  1067. -- The module must be in the module graph and its source must be available.
  1068. -- Throws a 'HscTypes.SourceError' on parse error.
  1069. getTokenStream :: GhcMonad m => Module -> m [Located Token]
  1070. getTokenStream mod = do
  1071. (sourceFile, source, flags) <- getModuleSourceAndFlags mod
  1072. let startLoc = mkRealSrcLoc (mkFastString sourceFile) 1 1
  1073. case lexTokenStream source startLoc flags of
  1074. POk _ ts -> return ts
  1075. PFailed span err ->
  1076. do dflags <- getDynFlags
  1077. liftIO $ throwIO $ mkSrcErr (unitBag $ mkPlainErrMsg dflags span err)
  1078. -- | Give even more information on the source than 'getTokenStream'
  1079. -- This function allows reconstructing the source completely with
  1080. -- 'showRichTokenStream'.
  1081. getRichTokenStream :: GhcMonad m => Module -> m [(Located Token, String)]
  1082. getRichTokenStream mod = do
  1083. (sourceFile, source, flags) <- getModuleSourceAndFlags mod
  1084. let startLoc = mkRealSrcLoc (mkFastString sourceFile) 1 1
  1085. case lexTokenStream source startLoc flags of
  1086. POk _ ts -> return $ addSourceToTokens startLoc source ts
  1087. PFailed span err ->
  1088. do dflags <- getDynFlags
  1089. liftIO $ throwIO $ mkSrcErr (unitBag $ mkPlainErrMsg dflags span err)
  1090. -- | Given a source location and a StringBuffer corresponding to this
  1091. -- location, return a rich token stream with the source associated to the
  1092. -- tokens.
  1093. addSourceToTokens :: RealSrcLoc -> StringBuffer -> [Located Token]
  1094. -> [(Located Token, String)]
  1095. addSourceToTokens _ _ [] = []
  1096. addSourceToTokens loc buf (t@(L span _) : ts)
  1097. = case span of
  1098. UnhelpfulSpan _ -> (t,"") : addSourceToTokens loc buf ts
  1099. RealSrcSpan s -> (t,str) : addSourceToTokens newLoc newBuf ts
  1100. where
  1101. (newLoc, newBuf, str) = go "" loc buf
  1102. start = realSrcSpanStart s
  1103. end = realSrcSpanEnd s
  1104. go acc loc buf | loc < start = go acc nLoc nBuf
  1105. | start <= loc && loc < end = go (ch:acc) nLoc nBuf
  1106. | otherwise = (loc, buf, reverse acc)
  1107. where (ch, nBuf) = nextChar buf
  1108. nLoc = advanceSrcLoc loc ch
  1109. -- | Take a rich token stream such as produced from 'getRichTokenStream' and
  1110. -- return source code almost identical to the original code (except for
  1111. -- insignificant whitespace.)
  1112. showRichTokenStream :: [(Located Token, String)] -> String
  1113. showRichTokenStream ts = go startLoc ts ""
  1114. where sourceFile = getFile $ map (getLoc . fst) ts
  1115. getFile [] = panic "showRichTokenStream: No source file found"
  1116. getFile (UnhelpfulSpan _ : xs) = getFile xs
  1117. getFile (RealSrcSpan s : _) = srcSpanFile s
  1118. startLoc = mkRealSrcLoc sourceFile 1 1
  1119. go _ [] = id
  1120. go loc ((L span _, str):ts)
  1121. = case span of
  1122. UnhelpfulSpan _ -> go loc ts
  1123. RealSrcSpan s
  1124. | locLine == tokLine -> ((replicate (tokCol - locCol) ' ') ++)
  1125. . (str ++)
  1126. . go tokEnd ts
  1127. | otherwise -> ((replicate (tokLine - locLine) '\n') ++)
  1128. . ((replicate (tokCol - 1) ' ') ++)
  1129. . (str ++)
  1130. . go tokEnd ts
  1131. where (locLine, locCol) = (srcLocLine loc, srcLocCol loc)
  1132. (tokLine, tokCol) = (srcSpanStartLine s, srcSpanStartCol s)
  1133. tokEnd = realSrcSpanEnd s
  1134. -- -----------------------------------------------------------------------------
  1135. -- Interactive evaluation
  1136. -- | Takes a 'ModuleName' and possibly a 'PackageId', and consults the
  1137. -- filesystem and package database to find the corresponding 'Module',
  1138. -- using the algorithm that is used for an @import@ declaration.
  1139. findModule :: GhcMonad m => ModuleName -> Maybe FastString -> m Module
  1140. findModule mod_name maybe_pkg = withSession $ \hsc_env -> do
  1141. let
  1142. dflags = hsc_dflags hsc_env
  1143. this_pkg = thisPackage dflags
  1144. --
  1145. case maybe_pkg of
  1146. Just pkg | fsToPackageId pkg /= this_pkg && pkg /= fsLit "this" -> liftIO $ do
  1147. res <- findImportedModule hsc_env mod_name maybe_pkg
  1148. case res of
  1149. Found _ m -> return m
  1150. err -> noModError dflags noSrcSpan mod_name err
  1151. _otherwise -> do
  1152. home <- lookupLoadedHomeModule mod_name
  1153. case home of
  1154. Just m -> return m
  1155. Nothing -> liftIO $ do
  1156. res <- findImportedModule hsc_env mod_name maybe_pkg
  1157. case res of
  1158. Found loc m | modulePackageId m /= this_pkg -> return m
  1159. | otherwise -> modNotLoadedError dflags m loc

Large files files are truncated, but you can click here to view the full file