{-# OPTIONS -#include "Linker.h" #-} ----------------------------------------------------------------------------- -- -- GHC Interactive User Interface -- -- (c) The GHC Team 2005 -- ----------------------------------------------------------------------------- module InteractiveUI ( interactiveUI, ghciWelcomeMsg ) where #include "HsVersions.h" -- The GHC interface import qualified GHC import GHC ( Session, verbosity, dopt, DynFlag(..), mkModule, pprModule, Type, Module, SuccessFlag(..), TyThing(..), Name, LoadHowMuch(..), GhcException(..), showGhcException ) import Outputable -- following all needed for :info... ToDo: remove import IfaceSyn ( IfaceDecl(..), IfaceClassOp(..), IfaceConDecls(..), IfaceConDecl(..), IfaceType, pprIfaceDeclHead, pprParendIfaceType, pprIfaceForAllPart, pprIfaceType ) import FunDeps ( pprFundeps ) import SrcLoc ( SrcLoc, isGoodSrcLoc ) import OccName ( OccName, parenSymOcc, occNameUserString ) import BasicTypes ( StrictnessMark(..), defaultFixity ) -- Other random utilities import Panic ( panic, installSignalHandlers ) import Config import StaticFlags ( opt_IgnoreDotGhci ) import Linker ( showLinkerState ) import Util ( removeSpaces, handle, global, toArgs, looksLikeModuleName, prefixMatch ) #ifndef mingw32_HOST_OS import Util ( handle ) import System.Posix #if __GLASGOW_HASKELL__ > 504 hiding (getEnv) #endif #endif #ifdef USE_READLINE import Control.Concurrent ( yield ) -- Used in readline loop import System.Console.Readline as Readline #endif --import SystemExts import Control.Exception as Exception import Data.Dynamic -- import Control.Concurrent import Numeric import Data.List import Data.Int ( Int64 ) import System.Cmd import System.CPUTime import System.Environment import System.Exit ( exitWith, ExitCode(..) ) import System.Directory import System.IO import System.IO.Error as IO import Data.Char import Control.Monad as Monad import Foreign.StablePtr ( newStablePtr ) import GHC.Exts ( unsafeCoerce# ) import GHC.IOBase ( IOErrorType(InvalidArgument) ) import Data.IORef ( IORef, newIORef, readIORef, writeIORef ) import System.Posix.Internals ( setNonBlockingFD ) ----------------------------------------------------------------------------- ghciWelcomeMsg = " ___ ___ _\n"++ " / _ \\ /\\ /\\/ __(_)\n"++ " / /_\\// /_/ / / | | GHC Interactive, version " ++ cProjectVersion ++ ", for Haskell 98.\n"++ "/ /_\\\\/ __ / /___| | http://www.haskell.org/ghc/\n"++ "\\____/\\/ /_/\\____/|_| Type :? for help.\n" GLOBAL_VAR(commands, builtin_commands, [(String, String -> GHCi Bool)]) builtin_commands :: [(String, String -> GHCi Bool)] builtin_commands = [ ("add", keepGoingPaths addModule), ("browse", keepGoing browseCmd), ("cd", keepGoing changeDirectory), ("def", keepGoing defineMacro), ("help", keepGoing help), ("?", keepGoing help), ("info", keepGoing info), ("load", keepGoingPaths loadModule), ("module", keepGoing setContext), ("reload", keepGoing reloadModule), ("set", keepGoing setCmd), ("show", keepGoing showCmd), ("type", keepGoing typeOfExpr), ("kind", keepGoing kindOfType), ("unset", keepGoing unsetOptions), ("undef", keepGoing undefineMacro), ("quit", quit) ] keepGoing :: (String -> GHCi ()) -> (String -> GHCi Bool) keepGoing a str = a str >> return False keepGoingPaths :: ([FilePath] -> GHCi ()) -> (String -> GHCi Bool) keepGoingPaths a str = a (toArgs str) >> return False shortHelpText = "use :? for help.\n" -- NOTE: spaces at the end of each line to workaround CPP/string gap bug. helpText = " Commands available from the prompt:\n" ++ "\n" ++ " evaluate/run \n" ++ " :add ... add module(s) to the current target set\n" ++ " :browse [*] display the names defined by \n" ++ " :cd change directory to \n" ++ " :def define a command :\n" ++ " :help, :? display this list of commands\n" ++ " :info [ ...] display information about the given names\n" ++ " :load ... load module(s) and their dependents\n" ++ " :module [+/-] [*] ... set the context for expression evaluation\n" ++ " :reload reload the current module set\n" ++ "\n" ++ " :set