PageRenderTime 73ms CodeModel.GetById 16ms RepoModel.GetById 0ms app.codeStats 0ms

/compiler/main/GHC.hs

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