{-# OPTIONS -fno-cse #-} -- -fno-cse is needed for GLOBAL_VAR's to behave properly {-# OPTIONS_GHC -fno-warn-name-shadowing #-} ----------------------------------------------------------------------------- -- -- GHC Interactive User Interface -- -- (c) The GHC Team 2005-2006 -- ----------------------------------------------------------------------------- module InteractiveUI ( interactiveUI, ghciWelcomeMsg ) where #include "HsVersions.h" import qualified GhciMonad import GhciMonad hiding (runStmt) import GhciTags import Debugger -- The GHC interface import qualified GHC hiding (resume, runStmt) import GHC ( LoadHowMuch(..), Target(..), TargetId(..), TyThing(..), Phase, BreakIndex, Resume, SingleStep, Ghc, handleSourceError ) import PprTyThing import DynFlags import Packages -- import PackageConfig import UniqFM import HscTypes ( implicitTyThings, handleFlagWarnings ) import qualified RdrName ( getGRE_NameQualifier_maybes ) -- should this come via GHC? import Outputable hiding (printForUser, printForUserPartWay) import Module -- for ModuleEnv import Name import SrcLoc -- Other random utilities import CmdLineParser import Digraph import BasicTypes hiding (isTopLevel) import Panic hiding (showException) import Config import StaticFlags import Linker import Util import NameSet import Maybes ( orElse, expectJust ) import FastString import Encoding import Foreign.C #ifndef mingw32_HOST_OS import System.Posix hiding (getEnv) #else import qualified System.Win32 #endif import System.Console.Haskeline as Haskeline import qualified System.Console.Haskeline.Encoding as Encoding import Control.Monad.Trans --import SystemExts import Exception hiding (catch, block, unblock) -- import Control.Concurrent import System.FilePath import qualified Data.ByteString.Char8 as BS import Data.List import Data.Maybe import System.Cmd import System.Environment import System.Exit ( exitWith, ExitCode(..) ) import System.Directory import System.IO import System.IO.Error as IO import Data.Char import Data.Array import Control.Monad as Monad import Text.Printf import Foreign import GHC.Exts ( unsafeCoerce# ) #if __GLASGOW_HASKELL__ >= 611 import GHC.IO.Exception ( IOErrorType(InvalidArgument) ) import GHC.IO.Handle ( hFlushAll ) #else import GHC.IOBase ( IOErrorType(InvalidArgument) ) #endif import GHC.TopHandler import Data.IORef ( IORef, readIORef, writeIORef ) ----------------------------------------------------------------------------- ghciWelcomeMsg :: String ghciWelcomeMsg = "GHCi, version " ++ cProjectVersion ++ ": http://www.haskell.org/ghc/ :? for help" cmdName :: Command -> String cmdName (n,_,_) = n GLOBAL_VAR(macros_ref, [], [Command]) builtin_commands :: [Command] builtin_commands = [ -- Hugs users are accustomed to :e, so make sure it doesn't overlap ("?", keepGoing help, noCompletion), ("add", keepGoingPaths addModule, completeFilename), ("abandon", keepGoing abandonCmd, noCompletion), ("break", keepGoing breakCmd, completeIdentifier), ("back", keepGoing backCmd, noCompletion), ("browse", keepGoing' (browseCmd False), completeModule), ("browse!", keepGoing' (browseCmd True), completeModule), ("cd", keepGoing' changeDirectory, completeFilename), ("check", keepGoing' checkModule, completeHomeModule), ("continue", keepGoing continueCmd, noCompletion), ("cmd", keepGoing cmdCmd, completeExpression), ("ctags", keepGoing createCTagsWithLineNumbersCmd, completeFilename), ("ctags!", keepGoing createCTagsWithRegExesCmd, completeFilename), ("def", keepGoing (defineMacro False), completeExpression), ("def!", keepGoing (defineMacro True), completeExpression), ("delete", keepGoing deleteCmd, noCompletion), ("edit", keepGoing editFile, completeFilename), ("etags", keepGoing createETagsFileCmd, completeFilename), ("force", keepGoing forceCmd, completeExpression), ("forward", keepGoing forwardCmd, noCompletion), ("help", keepGoing help, noCompletion), ("history", keepGoing historyCmd, noCompletion), ("info", keepGoing' info, completeIdentifier), ("kind", keepGoing' kindOfType, completeIdentifier), ("load", keepGoingPaths loadModule_, completeHomeModuleOrFile), ("list", keepGoing' listCmd, noCompletion), ("module", keepGoing setContext, completeModule), ("main", keepGoing runMain, completeFilename), ("print", keepGoing printCmd, completeExpression), ("quit", quit, noCompletion), ("reload", keepGoing' reloadModule, noCompletion), ("run", keepGoing runRun, completeFilename), ("set", keepGoing setCmd, completeSetOptions), ("show", keepGoing showCmd, completeShowOptions), ("sprint", keepGoing sprintCmd, completeExpression), ("step", keepGoing stepCmd, completeIdentifier), ("steplocal", keepGoing stepLocalCmd, completeIdentifier), ("stepmodule",keepGoing stepModuleCmd, completeIdentifier), ("type", keepGoing' typeOfExpr, completeExpression), ("trace", keepGoing traceCmd, completeExpression), ("undef", keepGoing undefineMacro, completeMacro), ("unset", keepGoing unsetOptions, completeSetOptions) ] -- We initialize readline (in the interactiveUI function) to use -- word_break_chars as the default set of completion word break characters. -- This can be overridden for a particular command (for example, filename -- expansion shouldn't consider '/' to be a word break) by setting the third -- entry in the Command tuple above. -- -- NOTE: in order for us to override the default correctly, any custom entry -- must be a SUBSET of word_break_chars. word_break_chars :: String word_break_chars = let symbols = "!#$%&*+/<=>?@\\^|-~" specials = "(),;[]`{}" spaces = " \t\n" in spaces ++ specials ++ symbols flagWordBreakChars :: String flagWordBreakChars = " \t\n" keepGoing :: (String -> GHCi ()) -> (String -> InputT GHCi Bool) keepGoing a str = keepGoing' (lift . a) str keepGoing' :: Monad m => (String -> m ()) -> String -> m Bool keepGoing' a str = a str >> return False keepGoingPaths :: ([FilePath] -> InputT GHCi ()) -> (String -> InputT GHCi Bool) keepGoingPaths a str = do case toArgs str of Left err -> Encoding.encode err >>= liftIO . BS.hPutStrLn stderr Right args -> a args return False shortHelpText :: String shortHelpText = "use :? for help.\n" helpText :: String helpText = " Commands available from the prompt:\n" ++ "\n" ++ " evaluate/run \n" ++ " : repeat last command\n" ++ " :{\\n ..lines.. \\n:}\\n multiline command\n" ++ " :add [*] ... add module(s) to the current target set\n" ++ " :browse[!] [[*]] display the names defined by module \n" ++ " (!: more details; *: all top-level names)\n" ++ " :cd change directory to \n" ++ " :cmd run the commands returned by ::IO String\n" ++ " :ctags[!] [] create tags file for Vi (default: \"tags\")\n" ++ " (!: use regex instead of line number)\n" ++ " :def define a command :\n" ++ " :edit edit file\n" ++ " :edit edit last module\n" ++ " :etags [] create tags file for Emacs (default: \"TAGS\")\n" ++ " :help, :? display this list of commands\n" ++ " :info [ ...] display information about the given names\n" ++ " :kind show the kind of \n" ++ " :load [*] ... load module(s) and their dependents\n" ++ " :main [ ...] run the main function with the given arguments\n" ++ " :module [+/-] [*] ... set the context for expression evaluation\n" ++ " :quit exit GHCi\n" ++ " :reload reload the current module set\n" ++ " :run function [ ...] run the function with the given arguments\n" ++ " :type show the type of \n" ++ " :undef undefine user-defined command :\n" ++ " :! run the shell command \n" ++ "\n" ++ " -- Commands for debugging:\n" ++ "\n" ++ " :abandon at a breakpoint, abandon current computation\n" ++ " :back go back in the history (after :trace)\n" ++ " :break [] [] set a breakpoint at the specified location\n" ++ " :break set a breakpoint on the specified function\n" ++ " :continue resume after a breakpoint\n" ++ " :delete delete the specified breakpoint\n" ++ " :delete * delete all breakpoints\n" ++ " :force print , forcing unevaluated parts\n" ++ " :forward go forward in the history (after :back)\n" ++ " :history [] after :trace, show the execution history\n" ++ " :list show the source code around current breakpoint\n" ++ " :list identifier show the source code for \n" ++ " :list [] show the source code around line number \n" ++ " :print [ ...] prints a value without forcing its computation\n" ++ " :sprint [ ...] simplifed version of :print\n" ++ " :step single-step after stopping at a breakpoint\n"++ " :step single-step into \n"++ " :steplocal single-step within the current top-level binding\n"++ " :stepmodule single-step restricted to the current module\n"++ " :trace trace after stopping at a breakpoint\n"++ " :trace evaluate with tracing on (see :history)\n"++ "\n" ++ " -- Commands for changing settings:\n" ++ "\n" ++ " :set