{-# LANGUAGE CPP, MagicHash, NondecreasingIndentation, TupleSections #-} {-# OPTIONS -fno-cse #-} -- -fno-cse is needed for GLOBAL_VAR's to behave properly ----------------------------------------------------------------------------- -- -- GHC Interactive User Interface -- -- (c) The GHC Team 2005-2006 -- ----------------------------------------------------------------------------- module InteractiveUI ( interactiveUI, GhciSettings(..), defaultGhciSettings, ghciCommands, ghciWelcomeMsg, makeHDL ) where #include "HsVersions.h" -- GHCi import qualified GhciMonad ( args, runStmt ) import GhciMonad hiding ( args, runStmt ) import GhciTags import Debugger -- The GHC interface import DynFlags import ErrUtils import GhcMonad ( modifySession ) import qualified GHC import GHC ( LoadHowMuch(..), Target(..), TargetId(..), InteractiveImport(..), TyThing(..), Phase, BreakIndex, Resume, SingleStep, Ghc, handleSourceError ) import HsImpExp import HscTypes ( tyThingParent_maybe, handleFlagWarnings, getSafeMode, hsc_IC, setInteractivePrintName ) import Module import Name import Packages ( trusted, getPackageDetails, listVisibleModuleNames, pprFlag ) import PprTyThing import RdrName ( getGRE_NameQualifier_maybes ) import SrcLoc import qualified Lexer import StringBuffer import Outputable hiding ( printForUser, printForUserPartWay, bold ) -- Other random utilities import BasicTypes hiding ( isTopLevel ) import Digraph import Encoding import FastString import Linker import Maybes ( orElse, expectJust ) import NameSet import Panic hiding ( showException ) import Util -- Haskell Libraries import System.Console.Haskeline as Haskeline import Control.Monad as Monad import Control.Applicative hiding (empty) import Control.Monad.Trans.Class import Control.Monad.IO.Class import Data.Array import qualified Data.ByteString.Char8 as BS import Data.Char import Data.Function import Data.IORef ( IORef, modifyIORef, newIORef, readIORef, writeIORef ) import Data.List ( find, group, intercalate, intersperse, isPrefixOf, nub, partition, sort, sortBy ) import Data.Maybe import Exception hiding (catch) import Foreign.C #if __GLASGOW_HASKELL__ >= 709 import Foreign #else import Foreign.Safe #endif import System.Directory import System.Environment import System.Exit ( exitWith, ExitCode(..) ) import System.FilePath import System.IO import System.IO.Error import System.IO.Unsafe ( unsafePerformIO ) import System.Process import Text.Printf import Text.Read ( readMaybe ) #ifndef mingw32_HOST_OS import System.Posix hiding ( getEnv ) #else import qualified System.Win32 #endif import GHC.Exts ( unsafeCoerce# ) import GHC.IO.Exception ( IOErrorType(InvalidArgument) ) import GHC.IO.Handle ( hFlushAll ) import GHC.TopHandler ( topHandler ) import qualified CLaSH.Backend import CLaSH.Backend.SystemVerilog (SystemVerilogState) import CLaSH.Backend.VHDL (VHDLState) import CLaSH.Backend.Verilog (VerilogState) import qualified CLaSH.Driver import CLaSH.Driver.Types (CLaSHOpts) import CLaSH.GHC.Evaluator import CLaSH.GHC.GenerateBindings import CLaSH.GHC.NetlistTypes import qualified CLaSH.Primitives.Util import CLaSH.Util (clashLibVersion) import qualified Data.Version as Data.Version import qualified Paths_clash_ghc ----------------------------------------------------------------------------- data GhciSettings = GhciSettings { availableCommands :: [Command], shortHelpText :: String, fullHelpText :: String, defPrompt :: String, defPrompt2 :: String } defaultGhciSettings :: IORef CLaSHOpts -> GhciSettings defaultGhciSettings opts = GhciSettings { availableCommands = ghciCommands opts, shortHelpText = defShortHelpText, fullHelpText = defFullHelpText, defPrompt = default_prompt, defPrompt2 = default_prompt2 } ghciWelcomeMsg :: String ghciWelcomeMsg = "CLaSHi, version " ++ Data.Version.showVersion Paths_clash_ghc.version ++ " (using clash-lib, version " ++ Data.Version.showVersion clashLibVersion ++ "):\nhttp://www.clash-lang.org/ :? for help" cmdName :: Command -> String cmdName (n,_,_) = n GLOBAL_VAR(macros_ref, [], [Command]) ghciCommands :: IORef CLaSHOpts -> [Command] ghciCommands opts = [ -- 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), ("complete", keepGoing completeCmd, 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 False), completeIdentifier), ("info!", keepGoing' (info True), completeIdentifier), ("issafe", keepGoing' isSafeCmd, completeModule), ("kind", keepGoing' (kindOfType False), completeIdentifier), ("kind!", keepGoing' (kindOfType True), completeIdentifier), ("load", keepGoingPaths loadModule_, completeHomeModuleOrFile), ("list", keepGoing' listCmd, noCompletion), ("module", keepGoing moduleCmd, completeSetModule), ("main", keepGoing runMain, completeFilename), ("print", keepGoing printCmd, completeExpression), ("quit", quit, noCompletion), ("reload", keepGoing' reloadModule, noCompletion), ("run", keepGoing runRun, completeFilename), ("script", keepGoing' scriptCmd, completeFilename), ("set", keepGoing setCmd, completeSetOptions), ("seti", keepGoing setiCmd, completeSeti), ("show", keepGoing showCmd, completeShowOptions), ("showi", keepGoing showiCmd, completeShowiOptions), ("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), ("vhdl", keepGoingPaths (makeVHDL opts), completeHomeModuleOrFile), ("verilog", keepGoingPaths (makeVerilog opts), completeHomeModuleOrFile), ("systemverilog", keepGoingPaths (makeSystemVerilog opts), completeHomeModuleOrFile) ] -- 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 -> liftIO $ hPutStrLn stderr err Right args -> a args return False defShortHelpText :: String defShortHelpText = "use :? for help.\n" defFullHelpText :: String defFullHelpText = " 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" ++ " :complete [] list completions for partial input string\n" ++ " :ctags[!] [] create tags file for Vi (default: \"tags\")\n" ++ " (!: use regex instead of line number)\n" ++ " :def define command : (later defined command has\n" ++ " precedence, :: is always a builtin 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" ++ " (!: do not filter instances)\n" ++ " :issafe [] display safe haskell information of module \n" ++ " :kind[!] show the kind of \n" ++ " (!: also print the normalised type)\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" ++ " :script run the script \n" ++ " :type show the type of \n" ++ " :undef undefine user-defined command :\n" ++ " :! run the shell command \n" ++ " :vhdl synthesize currently loaded module to vhdl\n" ++ " :vhdl [] synthesize specified modules/files to vhdl\n" ++ " :verilog synthesize currently loaded module to verilog\n" ++ " :verilog [] synthesize specified modules/files to verilog\n" ++ " :systemverilog synthesize currently loaded module to systemverilog\n" ++ " :systemverilog [] synthesize specified modules/files to systemverilog\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 show the source code for \n" ++ " :list [] show the source code around line number \n" ++ " :print [ ...] show a value without forcing its computation\n" ++ " :sprint [ ...] simplified 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