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

/ghc/InteractiveUI.hs

https://github.com/crdueck/ghc
Haskell | 3091 lines | 2314 code | 414 blank | 363 comment | 147 complexity | 2e7242efd9db5c4141470da19f285f54 MD5 | raw file

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

  1. {-# OPTIONS -fno-cse #-}
  2. -- -fno-cse is needed for GLOBAL_VAR's to behave properly
  3. -----------------------------------------------------------------------------
  4. --
  5. -- GHC Interactive User Interface
  6. --
  7. -- (c) The GHC Team 2005-2006
  8. --
  9. -----------------------------------------------------------------------------
  10. module InteractiveUI (
  11. interactiveUI,
  12. GhciSettings(..),
  13. defaultGhciSettings,
  14. ghciCommands,
  15. ghciWelcomeMsg
  16. ) where
  17. #include "HsVersions.h"
  18. -- GHCi
  19. import qualified GhciMonad ( args, runStmt )
  20. import GhciMonad hiding ( args, runStmt )
  21. import GhciTags
  22. import Debugger
  23. -- The GHC interface
  24. import DynFlags
  25. import GhcMonad ( modifySession )
  26. import qualified GHC
  27. import GHC ( LoadHowMuch(..), Target(..), TargetId(..), InteractiveImport(..),
  28. TyThing(..), Phase, BreakIndex, Resume, SingleStep, Ghc,
  29. handleSourceError )
  30. import HsImpExp
  31. import HscTypes ( tyThingParent_maybe, handleFlagWarnings, getSafeMode, hsc_IC,
  32. setInteractivePrintName )
  33. import Module
  34. import Name
  35. import Packages ( trusted, getPackageDetails, exposed, exposedModules, pkgIdMap )
  36. import PprTyThing
  37. import RdrName ( getGRE_NameQualifier_maybes )
  38. import SrcLoc
  39. import qualified Lexer
  40. import StringBuffer
  41. import UniqFM ( eltsUFM )
  42. import Outputable hiding ( printForUser, printForUserPartWay, bold )
  43. -- Other random utilities
  44. import BasicTypes hiding ( isTopLevel )
  45. import Config
  46. import Digraph
  47. import Encoding
  48. import FastString
  49. import Linker
  50. import Maybes ( orElse, expectJust )
  51. import NameSet
  52. import Panic hiding ( showException )
  53. import Util
  54. -- Haskell Libraries
  55. import System.Console.Haskeline as Haskeline
  56. import Control.Applicative hiding (empty)
  57. import Control.Monad as Monad
  58. import Control.Monad.Trans.Class
  59. import Control.Monad.IO.Class
  60. import Data.Array
  61. import qualified Data.ByteString.Char8 as BS
  62. import Data.Char
  63. import Data.Function
  64. import Data.IORef ( IORef, readIORef, writeIORef )
  65. import Data.List ( find, group, intercalate, intersperse, isPrefixOf, nub,
  66. partition, sort, sortBy )
  67. import Data.Maybe
  68. import Exception hiding (catch)
  69. import Foreign.C
  70. import Foreign.Safe
  71. import System.Directory
  72. import System.Environment
  73. import System.Exit ( exitWith, ExitCode(..) )
  74. import System.FilePath
  75. import System.IO
  76. import System.IO.Error
  77. import System.IO.Unsafe ( unsafePerformIO )
  78. import System.Process
  79. import Text.Printf
  80. import Text.Read ( readMaybe )
  81. #ifndef mingw32_HOST_OS
  82. import System.Posix hiding ( getEnv )
  83. #else
  84. import qualified System.Win32
  85. #endif
  86. import GHC.Exts ( unsafeCoerce# )
  87. import GHC.IO.Exception ( IOErrorType(InvalidArgument) )
  88. import GHC.IO.Handle ( hFlushAll )
  89. import GHC.TopHandler ( topHandler )
  90. -----------------------------------------------------------------------------
  91. data GhciSettings = GhciSettings {
  92. availableCommands :: [Command],
  93. shortHelpText :: String,
  94. fullHelpText :: String,
  95. defPrompt :: String,
  96. defPrompt2 :: String
  97. }
  98. defaultGhciSettings :: GhciSettings
  99. defaultGhciSettings =
  100. GhciSettings {
  101. availableCommands = ghciCommands,
  102. shortHelpText = defShortHelpText,
  103. fullHelpText = defFullHelpText,
  104. defPrompt = default_prompt,
  105. defPrompt2 = default_prompt2
  106. }
  107. ghciWelcomeMsg :: String
  108. ghciWelcomeMsg = "GHCi, version " ++ cProjectVersion ++
  109. ": http://www.haskell.org/ghc/ :? for help"
  110. cmdName :: Command -> String
  111. cmdName (n,_,_) = n
  112. GLOBAL_VAR(macros_ref, [], [Command])
  113. ghciCommands :: [Command]
  114. ghciCommands = [
  115. -- Hugs users are accustomed to :e, so make sure it doesn't overlap
  116. ("?", keepGoing help, noCompletion),
  117. ("add", keepGoingPaths addModule, completeFilename),
  118. ("abandon", keepGoing abandonCmd, noCompletion),
  119. ("break", keepGoing breakCmd, completeIdentifier),
  120. ("back", keepGoing backCmd, noCompletion),
  121. ("browse", keepGoing' (browseCmd False), completeModule),
  122. ("browse!", keepGoing' (browseCmd True), completeModule),
  123. ("cd", keepGoing' changeDirectory, completeFilename),
  124. ("check", keepGoing' checkModule, completeHomeModule),
  125. ("continue", keepGoing continueCmd, noCompletion),
  126. ("complete", keepGoing completeCmd, noCompletion),
  127. ("cmd", keepGoing cmdCmd, completeExpression),
  128. ("ctags", keepGoing createCTagsWithLineNumbersCmd, completeFilename),
  129. ("ctags!", keepGoing createCTagsWithRegExesCmd, completeFilename),
  130. ("def", keepGoing (defineMacro False), completeExpression),
  131. ("def!", keepGoing (defineMacro True), completeExpression),
  132. ("delete", keepGoing deleteCmd, noCompletion),
  133. ("edit", keepGoing' editFile, completeFilename),
  134. ("etags", keepGoing createETagsFileCmd, completeFilename),
  135. ("force", keepGoing forceCmd, completeExpression),
  136. ("forward", keepGoing forwardCmd, noCompletion),
  137. ("help", keepGoing help, noCompletion),
  138. ("history", keepGoing historyCmd, noCompletion),
  139. ("info", keepGoing' (info False), completeIdentifier),
  140. ("info!", keepGoing' (info True), completeIdentifier),
  141. ("issafe", keepGoing' isSafeCmd, completeModule),
  142. ("kind", keepGoing' (kindOfType False), completeIdentifier),
  143. ("kind!", keepGoing' (kindOfType True), completeIdentifier),
  144. ("load", keepGoingPaths loadModule_, completeHomeModuleOrFile),
  145. ("list", keepGoing' listCmd, noCompletion),
  146. ("module", keepGoing moduleCmd, completeSetModule),
  147. ("main", keepGoing runMain, completeFilename),
  148. ("print", keepGoing printCmd, completeExpression),
  149. ("quit", quit, noCompletion),
  150. ("reload", keepGoing' reloadModule, noCompletion),
  151. ("run", keepGoing runRun, completeFilename),
  152. ("script", keepGoing' scriptCmd, completeFilename),
  153. ("set", keepGoing setCmd, completeSetOptions),
  154. ("seti", keepGoing setiCmd, completeSeti),
  155. ("show", keepGoing showCmd, completeShowOptions),
  156. ("showi", keepGoing showiCmd, completeShowiOptions),
  157. ("sprint", keepGoing sprintCmd, completeExpression),
  158. ("step", keepGoing stepCmd, completeIdentifier),
  159. ("steplocal", keepGoing stepLocalCmd, completeIdentifier),
  160. ("stepmodule",keepGoing stepModuleCmd, completeIdentifier),
  161. ("type", keepGoing' typeOfExpr, completeExpression),
  162. ("trace", keepGoing traceCmd, completeExpression),
  163. ("undef", keepGoing undefineMacro, completeMacro),
  164. ("unset", keepGoing unsetOptions, completeSetOptions)
  165. ]
  166. -- We initialize readline (in the interactiveUI function) to use
  167. -- word_break_chars as the default set of completion word break characters.
  168. -- This can be overridden for a particular command (for example, filename
  169. -- expansion shouldn't consider '/' to be a word break) by setting the third
  170. -- entry in the Command tuple above.
  171. --
  172. -- NOTE: in order for us to override the default correctly, any custom entry
  173. -- must be a SUBSET of word_break_chars.
  174. word_break_chars :: String
  175. word_break_chars = let symbols = "!#$%&*+/<=>?@\\^|-~"
  176. specials = "(),;[]`{}"
  177. spaces = " \t\n"
  178. in spaces ++ specials ++ symbols
  179. flagWordBreakChars :: String
  180. flagWordBreakChars = " \t\n"
  181. keepGoing :: (String -> GHCi ()) -> (String -> InputT GHCi Bool)
  182. keepGoing a str = keepGoing' (lift . a) str
  183. keepGoing' :: Monad m => (String -> m ()) -> String -> m Bool
  184. keepGoing' a str = a str >> return False
  185. keepGoingPaths :: ([FilePath] -> InputT GHCi ()) -> (String -> InputT GHCi Bool)
  186. keepGoingPaths a str
  187. = do case toArgs str of
  188. Left err -> liftIO $ hPutStrLn stderr err
  189. Right args -> a args
  190. return False
  191. defShortHelpText :: String
  192. defShortHelpText = "use :? for help.\n"
  193. defFullHelpText :: String
  194. defFullHelpText =
  195. " Commands available from the prompt:\n" ++
  196. "\n" ++
  197. " <statement> evaluate/run <statement>\n" ++
  198. " : repeat last command\n" ++
  199. " :{\\n ..lines.. \\n:}\\n multiline command\n" ++
  200. " :add [*]<module> ... add module(s) to the current target set\n" ++
  201. " :browse[!] [[*]<mod>] display the names defined by module <mod>\n" ++
  202. " (!: more details; *: all top-level names)\n" ++
  203. " :cd <dir> change directory to <dir>\n" ++
  204. " :cmd <expr> run the commands returned by <expr>::IO String\n" ++
  205. " :complete <dom> [<rng>] <s> list completions for partial input string\n" ++
  206. " :ctags[!] [<file>] create tags file for Vi (default: \"tags\")\n" ++
  207. " (!: use regex instead of line number)\n" ++
  208. " :def <cmd> <expr> define command :<cmd> (later defined command has\n" ++
  209. " precedence, ::<cmd> is always a builtin command)\n" ++
  210. " :edit <file> edit file\n" ++
  211. " :edit edit last module\n" ++
  212. " :etags [<file>] create tags file for Emacs (default: \"TAGS\")\n" ++
  213. " :help, :? display this list of commands\n" ++
  214. " :info[!] [<name> ...] display information about the given names\n" ++
  215. " (!: do not filter instances)\n" ++
  216. " :issafe [<mod>] display safe haskell information of module <mod>\n" ++
  217. " :kind <type> show the kind of <type>\n" ++
  218. " :load [*]<module> ... load module(s) and their dependents\n" ++
  219. " :main [<arguments> ...] run the main function with the given arguments\n" ++
  220. " :module [+/-] [*]<mod> ... set the context for expression evaluation\n" ++
  221. " :quit exit GHCi\n" ++
  222. " :reload reload the current module set\n" ++
  223. " :run function [<arguments> ...] run the function with the given arguments\n" ++
  224. " :script <filename> run the script <filename>\n" ++
  225. " :type <expr> show the type of <expr>\n" ++
  226. " :undef <cmd> undefine user-defined command :<cmd>\n" ++
  227. " :!<command> run the shell command <command>\n" ++
  228. "\n" ++
  229. " -- Commands for debugging:\n" ++
  230. "\n" ++
  231. " :abandon at a breakpoint, abandon current computation\n" ++
  232. " :back go back in the history (after :trace)\n" ++
  233. " :break [<mod>] <l> [<col>] set a breakpoint at the specified location\n" ++
  234. " :break <name> set a breakpoint on the specified function\n" ++
  235. " :continue resume after a breakpoint\n" ++
  236. " :delete <number> delete the specified breakpoint\n" ++
  237. " :delete * delete all breakpoints\n" ++
  238. " :force <expr> print <expr>, forcing unevaluated parts\n" ++
  239. " :forward go forward in the history (after :back)\n" ++
  240. " :history [<n>] after :trace, show the execution history\n" ++
  241. " :list show the source code around current breakpoint\n" ++
  242. " :list identifier show the source code for <identifier>\n" ++
  243. " :list [<module>] <line> show the source code around line number <line>\n" ++
  244. " :print [<name> ...] prints a value without forcing its computation\n" ++
  245. " :sprint [<name> ...] simplifed version of :print\n" ++
  246. " :step single-step after stopping at a breakpoint\n"++
  247. " :step <expr> single-step into <expr>\n"++
  248. " :steplocal single-step within the current top-level binding\n"++
  249. " :stepmodule single-step restricted to the current module\n"++
  250. " :trace trace after stopping at a breakpoint\n"++
  251. " :trace <expr> evaluate <expr> with tracing on (see :history)\n"++
  252. "\n" ++
  253. " -- Commands for changing settings:\n" ++
  254. "\n" ++
  255. " :set <option> ... set options\n" ++
  256. " :seti <option> ... set options for interactive evaluation only\n" ++
  257. " :set args <arg> ... set the arguments returned by System.getArgs\n" ++
  258. " :set prog <progname> set the value returned by System.getProgName\n" ++
  259. " :set prompt <prompt> set the prompt used in GHCi\n" ++
  260. " :set prompt2 <prompt> set the continuation prompt used in GHCi\n" ++
  261. " :set editor <cmd> set the command used for :edit\n" ++
  262. " :set stop [<n>] <cmd> set the command to run when a breakpoint is hit\n" ++
  263. " :unset <option> ... unset options\n" ++
  264. "\n" ++
  265. " Options for ':set' and ':unset':\n" ++
  266. "\n" ++
  267. " +m allow multiline commands\n" ++
  268. " +r revert top-level expressions after each evaluation\n" ++
  269. " +s print timing/memory stats after each evaluation\n" ++
  270. " +t print type after evaluation\n" ++
  271. " -<flags> most GHC command line flags can also be set here\n" ++
  272. " (eg. -v2, -fglasgow-exts, etc.)\n" ++
  273. " for GHCi-specific flags, see User's Guide,\n"++
  274. " Flag reference, Interactive-mode options\n" ++
  275. "\n" ++
  276. " -- Commands for displaying information:\n" ++
  277. "\n" ++
  278. " :show bindings show the current bindings made at the prompt\n" ++
  279. " :show breaks show the active breakpoints\n" ++
  280. " :show context show the breakpoint context\n" ++
  281. " :show imports show the current imports\n" ++
  282. " :show linker show current linker state\n" ++
  283. " :show modules show the currently loaded modules\n" ++
  284. " :show packages show the currently active package flags\n" ++
  285. " :show language show the currently active language flags\n" ++
  286. " :show <setting> show value of <setting>, which is one of\n" ++
  287. " [args, prog, prompt, editor, stop]\n" ++
  288. " :showi language show language flags for interactive evaluation\n" ++
  289. "\n"
  290. findEditor :: IO String
  291. findEditor = do
  292. getEnv "EDITOR"
  293. `catchIO` \_ -> do
  294. #if mingw32_HOST_OS
  295. win <- System.Win32.getWindowsDirectory
  296. return (win </> "notepad.exe")
  297. #else
  298. return ""
  299. #endif
  300. foreign import ccall unsafe "rts_isProfiled" isProfiled :: IO CInt
  301. default_progname, default_prompt, default_prompt2, default_stop :: String
  302. default_progname = "<interactive>"
  303. default_prompt = "%s> "
  304. default_prompt2 = "%s| "
  305. default_stop = ""
  306. default_args :: [String]
  307. default_args = []
  308. interactiveUI :: GhciSettings -> [(FilePath, Maybe Phase)] -> Maybe [String]
  309. -> Ghc ()
  310. interactiveUI config srcs maybe_exprs = do
  311. -- although GHCi compiles with -prof, it is not usable: the byte-code
  312. -- compiler and interpreter don't work with profiling. So we check for
  313. -- this up front and emit a helpful error message (#2197)
  314. i <- liftIO $ isProfiled
  315. when (i /= 0) $
  316. throwGhcException (InstallationError "GHCi cannot be used when compiled with -prof")
  317. -- HACK! If we happen to get into an infinite loop (eg the user
  318. -- types 'let x=x in x' at the prompt), then the thread will block
  319. -- on a blackhole, and become unreachable during GC. The GC will
  320. -- detect that it is unreachable and send it the NonTermination
  321. -- exception. However, since the thread is unreachable, everything
  322. -- it refers to might be finalized, including the standard Handles.
  323. -- This sounds like a bug, but we don't have a good solution right
  324. -- now.
  325. _ <- liftIO $ newStablePtr stdin
  326. _ <- liftIO $ newStablePtr stdout
  327. _ <- liftIO $ newStablePtr stderr
  328. -- Initialise buffering for the *interpreted* I/O system
  329. initInterpBuffering
  330. -- The initial set of DynFlags used for interactive evaluation is the same
  331. -- as the global DynFlags, plus -XExtendedDefaultRules and
  332. -- -XNoMonomorphismRestriction.
  333. dflags <- getDynFlags
  334. let dflags' = (`xopt_set` Opt_ExtendedDefaultRules)
  335. . (`xopt_unset` Opt_MonomorphismRestriction)
  336. $ dflags
  337. GHC.setInteractiveDynFlags dflags'
  338. liftIO $ when (isNothing maybe_exprs) $ do
  339. -- Only for GHCi (not runghc and ghc -e):
  340. -- Turn buffering off for the compiled program's stdout/stderr
  341. turnOffBuffering
  342. -- Turn buffering off for GHCi's stdout
  343. hFlush stdout
  344. hSetBuffering stdout NoBuffering
  345. -- We don't want the cmd line to buffer any input that might be
  346. -- intended for the program, so unbuffer stdin.
  347. hSetBuffering stdin NoBuffering
  348. #if defined(mingw32_HOST_OS)
  349. -- On Unix, stdin will use the locale encoding. The IO library
  350. -- doesn't do this on Windows (yet), so for now we use UTF-8,
  351. -- for consistency with GHC 6.10 and to make the tests work.
  352. hSetEncoding stdin utf8
  353. #endif
  354. default_editor <- liftIO $ findEditor
  355. startGHCi (runGHCi srcs maybe_exprs)
  356. GHCiState{ progname = default_progname,
  357. GhciMonad.args = default_args,
  358. prompt = defPrompt config,
  359. prompt2 = defPrompt2 config,
  360. stop = default_stop,
  361. editor = default_editor,
  362. options = [],
  363. line_number = 1,
  364. break_ctr = 0,
  365. breaks = [],
  366. tickarrays = emptyModuleEnv,
  367. ghci_commands = availableCommands config,
  368. last_command = Nothing,
  369. cmdqueue = [],
  370. remembered_ctx = [],
  371. transient_ctx = [],
  372. ghc_e = isJust maybe_exprs,
  373. short_help = shortHelpText config,
  374. long_help = fullHelpText config
  375. }
  376. return ()
  377. withGhcAppData :: (FilePath -> IO a) -> IO a -> IO a
  378. withGhcAppData right left = do
  379. either_dir <- tryIO (getAppUserDataDirectory "ghc")
  380. case either_dir of
  381. Right dir ->
  382. do createDirectoryIfMissing False dir `catchIO` \_ -> return ()
  383. right dir
  384. _ -> left
  385. runGHCi :: [(FilePath, Maybe Phase)] -> Maybe [String] -> GHCi ()
  386. runGHCi paths maybe_exprs = do
  387. dflags <- getDynFlags
  388. let
  389. read_dot_files = not (gopt Opt_IgnoreDotGhci dflags)
  390. current_dir = return (Just ".ghci")
  391. app_user_dir = liftIO $ withGhcAppData
  392. (\dir -> return (Just (dir </> "ghci.conf")))
  393. (return Nothing)
  394. home_dir = do
  395. either_dir <- liftIO $ tryIO (getEnv "HOME")
  396. case either_dir of
  397. Right home -> return (Just (home </> ".ghci"))
  398. _ -> return Nothing
  399. canonicalizePath' :: FilePath -> IO (Maybe FilePath)
  400. canonicalizePath' fp = liftM Just (canonicalizePath fp)
  401. `catchIO` \_ -> return Nothing
  402. sourceConfigFile :: FilePath -> GHCi ()
  403. sourceConfigFile file = do
  404. exists <- liftIO $ doesFileExist file
  405. when exists $ do
  406. dir_ok <- liftIO $ checkPerms (getDirectory file)
  407. file_ok <- liftIO $ checkPerms file
  408. when (dir_ok && file_ok) $ do
  409. either_hdl <- liftIO $ tryIO (openFile file ReadMode)
  410. case either_hdl of
  411. Left _e -> return ()
  412. -- NOTE: this assumes that runInputT won't affect the terminal;
  413. -- can we assume this will always be the case?
  414. -- This would be a good place for runFileInputT.
  415. Right hdl ->
  416. do runInputTWithPrefs defaultPrefs defaultSettings $
  417. runCommands $ fileLoop hdl
  418. liftIO (hClose hdl `catchIO` \_ -> return ())
  419. where
  420. getDirectory f = case takeDirectory f of "" -> "."; d -> d
  421. --
  422. setGHCContextFromGHCiState
  423. when (read_dot_files) $ do
  424. mcfgs0 <- sequence $ [ current_dir, app_user_dir, home_dir ] ++ map (return . Just ) (ghciScripts dflags)
  425. mcfgs <- liftIO $ mapM canonicalizePath' (catMaybes mcfgs0)
  426. mapM_ sourceConfigFile $ nub $ catMaybes mcfgs
  427. -- nub, because we don't want to read .ghci twice if the
  428. -- CWD is $HOME.
  429. -- Perform a :load for files given on the GHCi command line
  430. -- When in -e mode, if the load fails then we want to stop
  431. -- immediately rather than going on to evaluate the expression.
  432. when (not (null paths)) $ do
  433. ok <- ghciHandle (\e -> do showException e; return Failed) $
  434. -- TODO: this is a hack.
  435. runInputTWithPrefs defaultPrefs defaultSettings $
  436. loadModule paths
  437. when (isJust maybe_exprs && failed ok) $
  438. liftIO (exitWith (ExitFailure 1))
  439. installInteractivePrint (interactivePrint dflags) (isJust maybe_exprs)
  440. -- if verbosity is greater than 0, or we are connected to a
  441. -- terminal, display the prompt in the interactive loop.
  442. is_tty <- liftIO (hIsTerminalDevice stdin)
  443. let show_prompt = verbosity dflags > 0 || is_tty
  444. -- reset line number
  445. getGHCiState >>= \st -> setGHCiState st{line_number=1}
  446. case maybe_exprs of
  447. Nothing ->
  448. do
  449. -- enter the interactive loop
  450. runGHCiInput $ runCommands $ nextInputLine show_prompt is_tty
  451. Just exprs -> do
  452. -- just evaluate the expression we were given
  453. enqueueCommands exprs
  454. let hdle e = do st <- getGHCiState
  455. -- flush the interpreter's stdout/stderr on exit (#3890)
  456. flushInterpBuffers
  457. -- Jump through some hoops to get the
  458. -- current progname in the exception text:
  459. -- <progname>: <exception>
  460. liftIO $ withProgName (progname st)
  461. $ topHandler e
  462. -- this used to be topHandlerFastExit, see #2228
  463. runInputTWithPrefs defaultPrefs defaultSettings $ do
  464. runCommands' hdle (return Nothing)
  465. -- and finally, exit
  466. liftIO $ when (verbosity dflags > 0) $ putStrLn "Leaving GHCi."
  467. runGHCiInput :: InputT GHCi a -> GHCi a
  468. runGHCiInput f = do
  469. dflags <- getDynFlags
  470. histFile <- if gopt Opt_GhciHistory dflags
  471. then liftIO $ withGhcAppData (\dir -> return (Just (dir </> "ghci_history")))
  472. (return Nothing)
  473. else return Nothing
  474. runInputT
  475. (setComplete ghciCompleteWord $ defaultSettings {historyFile = histFile})
  476. f
  477. -- | How to get the next input line from the user
  478. nextInputLine :: Bool -> Bool -> InputT GHCi (Maybe String)
  479. nextInputLine show_prompt is_tty
  480. | is_tty = do
  481. prmpt <- if show_prompt then lift mkPrompt else return ""
  482. r <- getInputLine prmpt
  483. incrementLineNo
  484. return r
  485. | otherwise = do
  486. when show_prompt $ lift mkPrompt >>= liftIO . putStr
  487. fileLoop stdin
  488. -- NOTE: We only read .ghci files if they are owned by the current user,
  489. -- and aren't world writable. Otherwise, we could be accidentally
  490. -- running code planted by a malicious third party.
  491. -- Furthermore, We only read ./.ghci if . is owned by the current user
  492. -- and isn't writable by anyone else. I think this is sufficient: we
  493. -- don't need to check .. and ../.. etc. because "." always refers to
  494. -- the same directory while a process is running.
  495. checkPerms :: String -> IO Bool
  496. #ifdef mingw32_HOST_OS
  497. checkPerms _ = return True
  498. #else
  499. checkPerms name =
  500. handleIO (\_ -> return False) $ do
  501. st <- getFileStatus name
  502. me <- getRealUserID
  503. if fileOwner st /= me then do
  504. putStrLn $ "WARNING: " ++ name ++ " is owned by someone else, IGNORING!"
  505. return False
  506. else do
  507. let mode = System.Posix.fileMode st
  508. if (groupWriteMode == (mode `intersectFileModes` groupWriteMode))
  509. || (otherWriteMode == (mode `intersectFileModes` otherWriteMode))
  510. then do
  511. putStrLn $ "*** WARNING: " ++ name ++
  512. " is writable by someone else, IGNORING!"
  513. return False
  514. else return True
  515. #endif
  516. incrementLineNo :: InputT GHCi ()
  517. incrementLineNo = do
  518. st <- lift $ getGHCiState
  519. let ln = 1+(line_number st)
  520. lift $ setGHCiState st{line_number=ln}
  521. fileLoop :: Handle -> InputT GHCi (Maybe String)
  522. fileLoop hdl = do
  523. l <- liftIO $ tryIO $ hGetLine hdl
  524. case l of
  525. Left e | isEOFError e -> return Nothing
  526. | -- as we share stdin with the program, the program
  527. -- might have already closed it, so we might get a
  528. -- handle-closed exception. We therefore catch that
  529. -- too.
  530. isIllegalOperation e -> return Nothing
  531. | InvalidArgument <- etype -> return Nothing
  532. | otherwise -> liftIO $ ioError e
  533. where etype = ioeGetErrorType e
  534. -- treat InvalidArgument in the same way as EOF:
  535. -- this can happen if the user closed stdin, or
  536. -- perhaps did getContents which closes stdin at
  537. -- EOF.
  538. Right l' -> do
  539. incrementLineNo
  540. return (Just l')
  541. mkPrompt :: GHCi String
  542. mkPrompt = do
  543. imports <- GHC.getContext
  544. resumes <- GHC.getResumeContext
  545. context_bit <-
  546. case resumes of
  547. [] -> return empty
  548. r:_ -> do
  549. let ix = GHC.resumeHistoryIx r
  550. if ix == 0
  551. then return (brackets (ppr (GHC.resumeSpan r)) <> space)
  552. else do
  553. let hist = GHC.resumeHistory r !! (ix-1)
  554. pan <- GHC.getHistorySpan hist
  555. return (brackets (ppr (negate ix) <> char ':'
  556. <+> ppr pan) <> space)
  557. let
  558. dots | _:rs <- resumes, not (null rs) = text "... "
  559. | otherwise = empty
  560. rev_imports = reverse imports -- rightmost are the most recent
  561. modules_bit =
  562. hsep [ char '*' <> ppr m | IIModule m <- rev_imports ] <+>
  563. hsep (map ppr [ myIdeclName d | IIDecl d <- rev_imports ])
  564. -- use the 'as' name if there is one
  565. myIdeclName d | Just m <- ideclAs d = m
  566. | otherwise = unLoc (ideclName d)
  567. deflt_prompt = dots <> context_bit <> modules_bit
  568. f ('%':'s':xs) = deflt_prompt <> f xs
  569. f ('%':'%':xs) = char '%' <> f xs
  570. f (x:xs) = char x <> f xs
  571. f [] = empty
  572. st <- getGHCiState
  573. dflags <- getDynFlags
  574. return (showSDoc dflags (f (prompt st)))
  575. queryQueue :: GHCi (Maybe String)
  576. queryQueue = do
  577. st <- getGHCiState
  578. case cmdqueue st of
  579. [] -> return Nothing
  580. c:cs -> do setGHCiState st{ cmdqueue = cs }
  581. return (Just c)
  582. -- Reconfigurable pretty-printing Ticket #5461
  583. installInteractivePrint :: Maybe String -> Bool -> GHCi ()
  584. installInteractivePrint Nothing _ = return ()
  585. installInteractivePrint (Just ipFun) exprmode = do
  586. ok <- trySuccess $ do
  587. (name:_) <- GHC.parseName ipFun
  588. modifySession (\he -> let new_ic = setInteractivePrintName (hsc_IC he) name
  589. in he{hsc_IC = new_ic})
  590. return Succeeded
  591. when (failed ok && exprmode) $ liftIO (exitWith (ExitFailure 1))
  592. -- | The main read-eval-print loop
  593. runCommands :: InputT GHCi (Maybe String) -> InputT GHCi ()
  594. runCommands = runCommands' handler
  595. runCommands' :: (SomeException -> GHCi Bool) -- ^ Exception handler
  596. -> InputT GHCi (Maybe String) -> InputT GHCi ()
  597. runCommands' eh gCmd = do
  598. b <- ghandle (\e -> case fromException e of
  599. Just UserInterrupt -> return $ Just False
  600. _ -> case fromException e of
  601. Just ghce ->
  602. do liftIO (print (ghce :: GhcException))
  603. return Nothing
  604. _other ->
  605. liftIO (Exception.throwIO e))
  606. (runOneCommand eh gCmd)
  607. case b of
  608. Nothing -> return ()
  609. Just _ -> runCommands' eh gCmd
  610. -- | Evaluate a single line of user input (either :<command> or Haskell code)
  611. runOneCommand :: (SomeException -> GHCi Bool) -> InputT GHCi (Maybe String)
  612. -> InputT GHCi (Maybe Bool)
  613. runOneCommand eh gCmd = do
  614. -- run a previously queued command if there is one, otherwise get new
  615. -- input from user
  616. mb_cmd0 <- noSpace (lift queryQueue)
  617. mb_cmd1 <- maybe (noSpace gCmd) (return . Just) mb_cmd0
  618. case mb_cmd1 of
  619. Nothing -> return Nothing
  620. Just c -> ghciHandle (\e -> lift $ eh e >>= return . Just) $
  621. handleSourceError printErrorAndKeepGoing
  622. (doCommand c)
  623. -- source error's are handled by runStmt
  624. -- is the handler necessary here?
  625. where
  626. printErrorAndKeepGoing err = do
  627. GHC.printException err
  628. return $ Just True
  629. noSpace q = q >>= maybe (return Nothing)
  630. (\c -> case removeSpaces c of
  631. "" -> noSpace q
  632. ":{" -> multiLineCmd q
  633. c' -> return (Just c') )
  634. multiLineCmd q = do
  635. st <- lift getGHCiState
  636. let p = prompt st
  637. lift $ setGHCiState st{ prompt = prompt2 st }
  638. mb_cmd <- collectCommand q ""
  639. lift $ getGHCiState >>= \st' -> setGHCiState st'{ prompt = p }
  640. return mb_cmd
  641. -- we can't use removeSpaces for the sublines here, so
  642. -- multiline commands are somewhat more brittle against
  643. -- fileformat errors (such as \r in dos input on unix),
  644. -- we get rid of any extra spaces for the ":}" test;
  645. -- we also avoid silent failure if ":}" is not found;
  646. -- and since there is no (?) valid occurrence of \r (as
  647. -- opposed to its String representation, "\r") inside a
  648. -- ghci command, we replace any such with ' ' (argh:-(
  649. collectCommand q c = q >>=
  650. maybe (liftIO (ioError collectError))
  651. (\l->if removeSpaces l == ":}"
  652. then return (Just $ removeSpaces c)
  653. else collectCommand q (c ++ "\n" ++ map normSpace l))
  654. where normSpace '\r' = ' '
  655. normSpace x = x
  656. -- SDM (2007-11-07): is userError the one to use here?
  657. collectError = userError "unterminated multiline command :{ .. :}"
  658. -- | Handle a line of input
  659. doCommand :: String -> InputT GHCi (Maybe Bool)
  660. -- command
  661. doCommand (':' : cmd) = do
  662. result <- specialCommand cmd
  663. case result of
  664. True -> return Nothing
  665. _ -> return $ Just True
  666. -- haskell
  667. doCommand stmt = do
  668. ml <- lift $ isOptionSet Multiline
  669. if ml
  670. then do
  671. mb_stmt <- checkInputForLayout stmt gCmd
  672. case mb_stmt of
  673. Nothing -> return $ Just True
  674. Just ml_stmt -> do
  675. result <- timeIt $ lift $ runStmt ml_stmt GHC.RunToCompletion
  676. return $ Just result
  677. else do
  678. result <- timeIt $ lift $ runStmt stmt GHC.RunToCompletion
  679. return $ Just result
  680. -- #4316
  681. -- lex the input. If there is an unclosed layout context, request input
  682. checkInputForLayout :: String -> InputT GHCi (Maybe String)
  683. -> InputT GHCi (Maybe String)
  684. checkInputForLayout stmt getStmt = do
  685. dflags' <- lift $ getDynFlags
  686. let dflags = xopt_set dflags' Opt_AlternativeLayoutRule
  687. st0 <- lift $ getGHCiState
  688. let buf' = stringToStringBuffer stmt
  689. loc = mkRealSrcLoc (fsLit (progname st0)) (line_number st0) 1
  690. pstate = Lexer.mkPState dflags buf' loc
  691. case Lexer.unP goToEnd pstate of
  692. (Lexer.POk _ False) -> return $ Just stmt
  693. _other -> do
  694. st1 <- lift getGHCiState
  695. let p = prompt st1
  696. lift $ setGHCiState st1{ prompt = prompt2 st1 }
  697. mb_stmt <- ghciHandle (\ex -> case fromException ex of
  698. Just UserInterrupt -> return Nothing
  699. _ -> case fromException ex of
  700. Just ghce ->
  701. do liftIO (print (ghce :: GhcException))
  702. return Nothing
  703. _other -> liftIO (Exception.throwIO ex))
  704. getStmt
  705. lift $ getGHCiState >>= \st' -> setGHCiState st'{ prompt = p }
  706. -- the recursive call does not recycle parser state
  707. -- as we use a new string buffer
  708. case mb_stmt of
  709. Nothing -> return Nothing
  710. Just str -> if str == ""
  711. then return $ Just stmt
  712. else do
  713. checkInputForLayout (stmt++"\n"++str) getStmt
  714. where goToEnd = do
  715. eof <- Lexer.nextIsEOF
  716. if eof
  717. then Lexer.activeContext
  718. else Lexer.lexer return >> goToEnd
  719. enqueueCommands :: [String] -> GHCi ()
  720. enqueueCommands cmds = do
  721. st <- getGHCiState
  722. setGHCiState st{ cmdqueue = cmds ++ cmdqueue st }
  723. -- | If we one of these strings prefixes a command, then we treat it as a decl
  724. -- rather than a stmt.
  725. declPrefixes :: [String]
  726. declPrefixes = ["class ","data ","newtype ","type ","instance ", "deriving ",
  727. "foreign ", "default ", "default("]
  728. -- | Entry point to execute some haskell code from user
  729. runStmt :: String -> SingleStep -> GHCi Bool
  730. runStmt stmt step
  731. -- empty
  732. | null (filter (not.isSpace) stmt)
  733. = return False
  734. -- import
  735. | "import " `isPrefixOf` stmt
  736. = do addImportToContext stmt; return False
  737. -- data, class, newtype...
  738. | any (flip isPrefixOf stmt) declPrefixes
  739. = do _ <- liftIO $ tryIO $ hFlushAll stdin
  740. result <- GhciMonad.runDecls stmt
  741. afterRunStmt (const True) (GHC.RunOk result)
  742. | otherwise
  743. = do -- In the new IO library, read handles buffer data even if the Handle
  744. -- is set to NoBuffering. This causes problems for GHCi where there
  745. -- are really two stdin Handles. So we flush any bufferred data in
  746. -- GHCi's stdin Handle here (only relevant if stdin is attached to
  747. -- a file, otherwise the read buffer can't be flushed).
  748. _ <- liftIO $ tryIO $ hFlushAll stdin
  749. m_result <- GhciMonad.runStmt stmt step
  750. case m_result of
  751. Nothing -> return False
  752. Just result -> afterRunStmt (const True) result
  753. -- | Clean up the GHCi environment after a statement has run
  754. afterRunStmt :: (SrcSpan -> Bool) -> GHC.RunResult -> GHCi Bool
  755. afterRunStmt _ (GHC.RunException e) = liftIO $ Exception.throwIO e
  756. afterRunStmt step_here run_result = do
  757. resumes <- GHC.getResumeContext
  758. case run_result of
  759. GHC.RunOk names -> do
  760. show_types <- isOptionSet ShowType
  761. when show_types $ printTypeOfNames names
  762. GHC.RunBreak _ names mb_info
  763. | isNothing mb_info ||
  764. step_here (GHC.resumeSpan $ head resumes) -> do
  765. mb_id_loc <- toBreakIdAndLocation mb_info
  766. let bCmd = maybe "" ( \(_,l) -> onBreakCmd l ) mb_id_loc
  767. if (null bCmd)
  768. then printStoppedAtBreakInfo (head resumes) names
  769. else enqueueCommands [bCmd]
  770. -- run the command set with ":set stop <cmd>"
  771. st <- getGHCiState
  772. enqueueCommands [stop st]
  773. return ()
  774. | otherwise -> resume step_here GHC.SingleStep >>=
  775. afterRunStmt step_here >> return ()
  776. _ -> return ()
  777. flushInterpBuffers
  778. liftIO installSignalHandlers
  779. b <- isOptionSet RevertCAFs
  780. when b revertCAFs
  781. return (case run_result of GHC.RunOk _ -> True; _ -> False)
  782. toBreakIdAndLocation ::
  783. Maybe GHC.BreakInfo -> GHCi (Maybe (Int, BreakLocation))
  784. toBreakIdAndLocation Nothing = return Nothing
  785. toBreakIdAndLocation (Just inf) = do
  786. let md = GHC.breakInfo_module inf
  787. nm = GHC.breakInfo_number inf
  788. st <- getGHCiState
  789. return $ listToMaybe [ id_loc | id_loc@(_,loc) <- breaks st,
  790. breakModule loc == md,
  791. breakTick loc == nm ]
  792. printStoppedAtBreakInfo :: Resume -> [Name] -> GHCi ()
  793. printStoppedAtBreakInfo res names = do
  794. printForUser $ ptext (sLit "Stopped at") <+>
  795. ppr (GHC.resumeSpan res)
  796. -- printTypeOfNames session names
  797. let namesSorted = sortBy compareNames names
  798. tythings <- catMaybes `liftM` mapM GHC.lookupName namesSorted
  799. docs <- mapM pprTypeAndContents [i | AnId i <- tythings]
  800. printForUserPartWay $ vcat docs
  801. printTypeOfNames :: [Name] -> GHCi ()
  802. printTypeOfNames names
  803. = mapM_ (printTypeOfName ) $ sortBy compareNames names
  804. compareNames :: Name -> Name -> Ordering
  805. n1 `compareNames` n2 = compareWith n1 `compare` compareWith n2
  806. where compareWith n = (getOccString n, getSrcSpan n)
  807. printTypeOfName :: Name -> GHCi ()
  808. printTypeOfName n
  809. = do maybe_tything <- GHC.lookupName n
  810. case maybe_tything of
  811. Nothing -> return ()
  812. Just thing -> printTyThing thing
  813. data MaybeCommand = GotCommand Command | BadCommand | NoLastCommand
  814. -- | Entry point for execution a ':<command>' input from user
  815. specialCommand :: String -> InputT GHCi Bool
  816. specialCommand ('!':str) = lift $ shellEscape (dropWhile isSpace str)
  817. specialCommand str = do
  818. let (cmd,rest) = break isSpace str
  819. maybe_cmd <- lift $ lookupCommand cmd
  820. htxt <- lift $ short_help `fmap` getGHCiState
  821. case maybe_cmd of
  822. GotCommand (_,f,_) -> f (dropWhile isSpace rest)
  823. BadCommand ->
  824. do liftIO $ hPutStr stdout ("unknown command ':" ++ cmd ++ "'\n"
  825. ++ htxt)
  826. return False
  827. NoLastCommand ->
  828. do liftIO $ hPutStr stdout ("there is no last command to perform\n"
  829. ++ htxt)
  830. return False
  831. shellEscape :: String -> GHCi Bool
  832. shellEscape str = liftIO (system str >> return False)
  833. lookupCommand :: String -> GHCi (MaybeCommand)
  834. lookupCommand "" = do
  835. st <- getGHCiState
  836. case last_command st of
  837. Just c -> return $ GotCommand c
  838. Nothing -> return NoLastCommand
  839. lookupCommand str = do
  840. mc <- lookupCommand' str
  841. st <- getGHCiState
  842. setGHCiState st{ last_command = mc }
  843. return $ case mc of
  844. Just c -> GotCommand c
  845. Nothing -> BadCommand
  846. lookupCommand' :: String -> GHCi (Maybe Command)
  847. lookupCommand' ":" = return Nothing
  848. lookupCommand' str' = do
  849. macros <- liftIO $ readIORef macros_ref
  850. ghci_cmds <- ghci_commands `fmap` getGHCiState
  851. let{ (str, cmds) = case str' of
  852. ':' : rest -> (rest, ghci_cmds) -- "::" selects a builtin command
  853. _ -> (str', ghci_cmds ++ macros) } -- otherwise prefer macros
  854. -- look for exact match first, then the first prefix match
  855. return $ case [ c | c <- cmds, str == cmdName c ] of
  856. c:_ -> Just c
  857. [] -> case [ c | c@(s,_,_) <- cmds, str `isPrefixOf` s ] of
  858. [] -> Nothing
  859. c:_ -> Just c
  860. getCurrentBreakSpan :: GHCi (Maybe SrcSpan)
  861. getCurrentBreakSpan = do
  862. resumes <- GHC.getResumeContext
  863. case resumes of
  864. [] -> return Nothing
  865. (r:_) -> do
  866. let ix = GHC.resumeHistoryIx r
  867. if ix == 0
  868. then return (Just (GHC.resumeSpan r))
  869. else do
  870. let hist = GHC.resumeHistory r !! (ix-1)
  871. pan <- GHC.getHistorySpan hist
  872. return (Just pan)
  873. getCurrentBreakModule :: GHCi (Maybe Module)
  874. getCurrentBreakModule = do
  875. resumes <- GHC.getResumeContext
  876. case resumes of
  877. [] -> return Nothing
  878. (r:_) -> do
  879. let ix = GHC.resumeHistoryIx r
  880. if ix == 0
  881. then return (GHC.breakInfo_module `liftM` GHC.resumeBreakInfo r)
  882. else do
  883. let hist = GHC.resumeHistory r !! (ix-1)
  884. return $ Just $ GHC.getHistoryModule hist
  885. -----------------------------------------------------------------------------
  886. --
  887. -- Commands
  888. --
  889. -----------------------------------------------------------------------------
  890. noArgs :: GHCi () -> String -> GHCi ()
  891. noArgs m "" = m
  892. noArgs _ _ = liftIO $ putStrLn "This command takes no arguments"
  893. withSandboxOnly :: String -> GHCi () -> GHCi ()
  894. withSandboxOnly cmd this = do
  895. dflags <- getDynFlags
  896. if not (gopt Opt_GhciSandbox dflags)
  897. then printForUser (text cmd <+>
  898. ptext (sLit "is not supported with -fno-ghci-sandbox"))
  899. else this
  900. -----------------------------------------------------------------------------
  901. -- :help
  902. help :: String -> GHCi ()
  903. help _ = do
  904. txt <- long_help `fmap` getGHCiState
  905. liftIO $ putStr txt
  906. -----------------------------------------------------------------------------
  907. -- :info
  908. info :: Bool -> String -> InputT GHCi ()
  909. info _ "" = throwGhcException (CmdLineError "syntax: ':i <thing-you-want-info-about>'")
  910. info allInfo s = handleSourceError GHC.printException $ do
  911. unqual <- GHC.getPrintUnqual
  912. dflags <- getDynFlags
  913. sdocs <- mapM (infoThing allInfo) (words s)
  914. mapM_ (liftIO . putStrLn . showSDocForUser dflags unqual) sdocs
  915. infoThing :: GHC.GhcMonad m => Bool -> String -> m SDoc
  916. infoThing allInfo str = do
  917. dflags <- getDynFlags
  918. let pefas = gopt Opt_PrintExplicitForalls dflags
  919. names <- GHC.parseName str
  920. mb_stuffs <- mapM (GHC.getInfo allInfo) names
  921. let filtered = filterOutChildren (\(t,_f,_ci,_fi) -> t) (catMaybes mb_stuffs)
  922. return $ vcat (intersperse (text "") $ map (pprInfo pefas) filtered)
  923. -- Filter out names whose parent is also there Good
  924. -- example is '[]', which is both a type and data
  925. -- constructor in the same type
  926. filterOutChildren :: (a -> TyThing) -> [a] -> [a]
  927. filterOutChildren get_thing xs
  928. = filterOut has_parent xs
  929. where
  930. all_names = mkNameSet (map (getName . get_thing) xs)
  931. has_parent x = case tyThingParent_maybe (get_thing x) of
  932. Just p -> getName p `elemNameSet` all_names
  933. Nothing -> False
  934. pprInfo :: PrintExplicitForalls
  935. -> (TyThing, Fixity, [GHC.ClsInst], [GHC.FamInst]) -> SDoc
  936. pprInfo pefas (thing, fixity, cls_insts, fam_insts)
  937. = pprTyThingInContextLoc pefas thing
  938. $$ show_fixity
  939. $$ vcat (map GHC.pprInstance cls_insts)
  940. $$ vcat (map GHC.pprFamInst fam_insts)
  941. where
  942. show_fixity
  943. | fixity == GHC.defaultFixity = empty
  944. | otherwise = ppr fixity <+> pprInfixName (GHC.getName thing)
  945. -----------------------------------------------------------------------------
  946. -- :main
  947. runMain :: String -> GHCi ()
  948. runMain s = case toArgs s of
  949. Left err -> liftIO (hPutStrLn stderr err)
  950. Right args ->
  951. do dflags <- getDynFlags
  952. case mainFunIs dflags of
  953. Nothing -> doWithArgs args "main"
  954. Just f -> doWithArgs args f
  955. -----------------------------------------------------------------------------
  956. -- :run
  957. runRun :: String -> GHCi ()
  958. runRun s = case toCmdArgs s of
  959. Left err -> liftIO (hPutStrLn stderr err)
  960. Right (cmd, args) -> doWithArgs args cmd
  961. doWithArgs :: [String] -> String -> GHCi ()
  962. doWithArgs args cmd = enqueueCommands ["System.Environment.withArgs " ++
  963. show args ++ " (" ++ cmd ++ ")"]
  964. -----------------------------------------------------------------------------
  965. -- :cd
  966. changeDirectory :: String -> InputT GHCi ()
  967. changeDirectory "" = do
  968. -- :cd on its own changes to the user's home directory
  969. either_dir <- liftIO $ tryIO getHomeDirectory
  970. case either_dir of
  971. Left _e -> return ()
  972. Right dir -> changeDirectory dir
  973. changeDirectory dir = do
  974. graph <- GHC.getModuleGraph
  975. when (not (null graph)) $
  976. liftIO $ putStrLn "Warning: changing directory causes all loaded modules to be unloaded,\nbecause the search path has changed."
  977. GHC.setTargets []
  978. _ <- GHC.load LoadAllTargets
  979. lift $ setContextAfterLoad False []
  980. GHC.workingDirectoryChanged
  981. dir' <- expandPath dir
  982. liftIO $ setCurrentDirectory dir'
  983. trySuccess :: GHC.GhcMonad m => m SuccessFlag -> m SuccessFlag
  984. trySuccess act =
  985. handleSourceError (\e -> do GHC.printException e
  986. return Failed) $ do
  987. act
  988. -----------------------------------------------------------------------------
  989. -- :edit
  990. editFile :: String -> InputT GHCi ()
  991. editFile str =
  992. do file <- if null str then lift chooseEditFile else return str
  993. st <- lift getGHCiState
  994. let cmd = editor st
  995. when (null cmd)
  996. $ throwGhcException (CmdLineError "editor not set, use :set editor")
  997. code <- liftIO $ system (cmd ++ ' ':file)
  998. when (code == ExitSuccess)
  999. $ reloadModule ""
  1000. -- The user didn't specify a file so we pick one for them.
  1001. -- Our strategy is to pick the first module that failed to load,
  1002. -- or otherwise the first target.
  1003. --
  1004. -- XXX: Can we figure out what happened if the depndecy analysis fails
  1005. -- (e.g., because the porgrammeer mistyped the name of a module)?
  1006. -- XXX: Can we figure out the location of an error to pass to the editor?
  1007. -- XXX: if we could figure out the list of errors that occured during the
  1008. -- last load/reaload, then we could start the editor focused on the first
  1009. -- of those.
  1010. chooseEditFile :: GHCi String
  1011. chooseEditFile =
  1012. do let hasFailed x = fmap not $ GHC.isLoaded $ GHC.ms_mod_name x
  1013. graph <- GHC.getModuleGraph
  1014. failed_graph <- filterM hasFailed graph
  1015. let order g = flattenSCCs $ GHC.topSortModuleGraph True g Nothing
  1016. pick xs = case xs of
  1017. x : _ -> GHC.ml_hs_file (GHC.ms_location x)
  1018. _ -> Nothing
  1019. case pick (order failed_graph) of
  1020. Just file -> return file
  1021. Nothing ->
  1022. do targets <- GHC.getTargets
  1023. case msum (map fromTarget targets) of
  1024. Just file -> return file
  1025. Nothing -> throwGhcException (CmdLineError "No files to edit.")
  1026. where fromTarget (GHC.Target (GHC.TargetFile f _) _ _) = Just f
  1027. fromTarget _ = Nothing -- when would we get a module target?
  1028. -----------------------------------------------------------------------------
  1029. -- :def
  1030. defineMacro :: Bool{-overwrite-} -> String -> GHCi ()
  1031. defineMacro _ (':':_) =
  1032. liftIO $ putStrLn "macro name cannot start with a colon"
  1033. defineMacro overwrite s = do
  1034. let (macro_name, definition) = break isSpace s
  1035. macros <- liftIO (readIORef macros_ref)
  1036. let defined = map cmdName macros
  1037. if (null macro_name)
  1038. then if null defined
  1039. then liftIO $ putStrLn "no macros defined"
  1040. else liftIO $ putStr ("the following macros are defined:\n" ++
  1041. unlines defined)
  1042. else do
  1043. if (not overwrite && macro_name `elem` defined)
  1044. then throwGhcException (CmdLineError
  1045. ("macro '" ++ macro_name ++ "' is already defined"))
  1046. else do
  1047. let filtered = [ cmd | cmd <- macros, cmdName cmd /= macro_name ]
  1048. -- give the expression a type signature, so we can be sure we're getting
  1049. -- something of the right type.
  1050. let new_expr = '(' : definition ++ ") :: String -> IO String"
  1051. -- compile the expression
  1052. handleSourceError (\e -> GHC.printException e) $
  1053. do
  1054. hv <- GHC.compileExpr new_expr
  1055. liftIO (writeIORef macros_ref -- later defined macros have precedence
  1056. ((macro_name, lift . runMacro hv, noCompletion) : filtered))
  1057. runMacro :: GHC.HValue{-String -> IO String-} -> String -> GHCi Bool
  1058. runMacro fun s = do
  1059. str <- liftIO ((unsafeCoerce# fun :: String -> IO String) s)
  1060. -- make sure we force any exceptions in the result, while we are still
  1061. -- inside the exception handler for commands:
  1062. seqList str (return ())
  1063. enqueueCommands (lines str)
  1064. return False
  1065. -----------------------------------------------------------------------------
  1066. -- :undef
  1067. undefineMacro :: String -> GHCi ()
  1068. undefineMacro str = mapM_ undef (words str)
  1069. where undef macro_name = do
  1070. cmds <- liftIO (readIORef macros_ref)
  1071. if (macro_name `notElem` map cmdName cmds)
  1072. then throwGhcException (CmdLineError
  1073. ("macro '" ++ macro_name ++ "' is not defined"))
  1074. else do
  1075. liftIO (writeIORef macros_ref (filter ((/= macro_name) . cmdName) cmds))
  1076. -----------------------------------------------------------------------------
  1077. -- :cmd
  1078. cmdCmd :: String -> GHCi ()
  1079. cmdCmd str = do
  1080. let expr = '(' : str ++ ") :: IO String"
  1081. handleSourceError (\e -> GHC.printException e) $
  1082. do
  1083. hv <- GHC.compileExpr expr
  1084. cmds <- liftIO $ (unsafeCoerce# hv :: IO String)
  1085. enqueueCommands (lines cmds)
  1086. return ()
  1087. -----------------------------------------------------------------------------
  1088. -- :check
  1089. checkModule :: String -> InputT GHCi ()
  1090. checkModule m = do
  1091. let modl = GHC.mkModuleName m
  1092. ok <- handleSourceError (\e -> GHC.printException e >> return False) $ do
  1093. r <- GHC.typecheckModule =<< GHC.parseModule =<< GHC.getModSummary modl
  1094. dflags <- getDynFlags
  1095. liftIO $ putStrLn $ showSDoc dflags $
  1096. case GHC.moduleInfo r of
  1097. cm | Just scope <- GHC.modInfoTopLevelScope cm ->
  1098. let
  1099. (loc, glob) = ASSERT( all isExternalName scope )
  1100. partition ((== modl) . GHC.moduleName . GHC.nameModule) scope
  1101. in
  1102. (text "global names: " <+> ppr glob) $$
  1103. (text "local names: " <+> ppr loc)

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