{-# OPTIONS_GHC -Wno-name-shadowing #-} {-# LANGUAGE BangPatterns #-} {-# LANGUAGE CPP #-} {-# LANGUAGE LambdaCase #-} {-# LANGUAGE MagicHash #-} {-# LANGUAGE MultiWayIf #-} {-# LANGUAGE NondecreasingIndentation #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE RecordWildCards #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TupleSections #-} {-# LANGUAGE ViewPatterns #-} ----------------------------------------------------------------------------- -- -- GHC Interactive User Interface -- -- (c) The GHC Team 2005-2006 -- ----------------------------------------------------------------------------- module Clash.GHCi.UI ( interactiveUI, GhciSettings(..), defaultGhciSettings, ghciCommands, ghciWelcomeMsg, makeHDL ) where #include "HsVersions.h" -- GHCi import qualified Clash.GHCi.UI.Monad as GhciMonad ( args, runStmt, runDecls' ) import Clash.GHCi.UI.Monad hiding ( args, runStmt ) import Clash.GHCi.UI.Tags import Clash.GHCi.UI.Info import Debugger -- The GHC interface import GHCi import GHCi.RemoteTypes import GHCi.BreakArray import DynFlags import ErrUtils hiding (traceCmd) import Finder import GhcMonad ( modifySession ) import qualified GHC import GHC ( LoadHowMuch(..), Target(..), TargetId(..), InteractiveImport(..), TyThing(..), Phase, BreakIndex, Resume, SingleStep, Ghc, GetDocsFailure(..), getModuleGraph, handleSourceError ) import HscMain (hscParseDeclsWithLocation, hscParseStmtWithLocation) import GHC.Hs.ImpExp import GHC.Hs import HscTypes ( tyThingParent_maybe, handleFlagWarnings, getSafeMode, hsc_IC, setInteractivePrintName, hsc_dflags, msObjFilePath, runInteractiveHsc, hsc_dynLinker ) import Module import Name import Packages ( trusted, getPackageDetails, getInstalledPackageDetails, listVisibleModuleNames, pprFlag ) import IfaceSyn ( showToHeader ) import PprTyThing import PrelNames import RdrName ( getGRE_NameQualifier_maybes, getRdrName ) import SrcLoc import qualified Lexer import StringBuffer import Outputable hiding ( printForUser, printForUserPartWay ) import DynamicLoading ( initializePlugins ) -- 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 import qualified GHC.LanguageExtensions as LangExt import Bag (unitBag) -- Haskell Libraries import System.Console.Haskeline as Haskeline import Control.Applicative hiding (empty) import Control.DeepSeq (deepseq) import Control.Monad as Monad import Control.Monad.IO.Class import Control.Monad.Trans.Class import Control.Monad.Trans.Except import Data.Array import qualified Data.ByteString.Char8 as BS import Data.Char import Data.Coerce import Data.Function import Data.IORef ( IORef, modifyIORef, newIORef, readIORef, writeIORef ) import Data.List ( find, group, intercalate, intersperse, isPrefixOf, isSuffixOf, nub, partition, sort, sortBy, (\\) ) import qualified Data.Set as S import Data.Maybe import Data.Map (Map) import qualified Data.Map as M import qualified Data.IntMap.Strict as IntMap import Data.Time.LocalTime ( getZonedTime ) import Data.Time.Format ( formatTime, defaultTimeLocale ) import Data.Version ( showVersion ) import Prelude hiding ((<>)) import Exception hiding (catch) import Foreign hiding (void) import GHC.Stack hiding (SrcLoc(..)) import System.Directory import System.Environment import System.Exit ( exitWith, ExitCode(..) ) import System.FilePath import System.Info import System.IO import System.IO.Error import System.IO.Unsafe ( unsafePerformIO ) import System.Process import Text.Printf import Text.Read ( readMaybe ) import Text.Read.Lex (isSymbolChar) import Unsafe.Coerce #if !defined(mingw32_HOST_OS) import System.Posix hiding ( getEnv ) #else import qualified System.Win32 #endif import GHC.IO.Exception ( IOErrorType(InvalidArgument) ) import GHC.IO.Handle ( hFlushAll ) import GHC.TopHandler ( topHandler ) import Clash.GHCi.Leak -- clash additions import qualified Clash.Backend import Clash.Backend (AggressiveXOptBB) import Clash.Backend.SystemVerilog (SystemVerilogState) import Clash.Backend.VHDL (VHDLState) import Clash.Backend.Verilog (VerilogState) import qualified Clash.Driver import Clash.Driver.Types (ClashOpts(..)) #if EXPERIMENTAL_EVALUATOR import Clash.GHC.PartialEval #else import Clash.GHC.Evaluator #endif import Clash.GHC.GenerateBindings import Clash.GHC.NetlistTypes import Clash.GHCi.Common import Clash.Netlist.BlackBox.Types (HdlSyn) import Clash.Netlist.Types (PreserveCase) import Clash.Util (clashLibVersion, reportTimeDiff) import qualified Data.Time.Clock as Clock import qualified Paths_clash_ghc import Clash.Annotations.BitRepresentation.Internal (buildCustomReprs) ----------------------------------------------------------------------------- data GhciSettings = GhciSettings { availableCommands :: [Command], shortHelpText :: String, fullHelpText :: String, defPrompt :: PromptFunction, defPromptCont :: PromptFunction } defaultGhciSettings :: IORef ClashOpts -> GhciSettings defaultGhciSettings opts = GhciSettings { availableCommands = ghciCommands opts, shortHelpText = defShortHelpText, defPrompt = default_prompt, defPromptCont = default_prompt_cont, fullHelpText = defFullHelpText } ghciWelcomeMsg :: String ghciWelcomeMsg = "Clashi, version " ++ Data.Version.showVersion Paths_clash_ghc.version ++ " (using clash-lib, version " ++ Data.Version.showVersion clashLibVersion ++ "):\nhttps://clash-lang.org/ :? for help" ghciCommands :: IORef ClashOpts -> [Command] ghciCommands opts = map mkCmd [ -- 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), ("disable", keepGoing disableCmd, noCompletion), ("doc", keepGoing' docCmd, completeIdentifier), ("edit", keepGoing' editFile, completeFilename), ("enable", keepGoing enableCmd, noCompletion), ("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), ("load!", keepGoingPaths loadModuleDefer, completeHomeModuleOrFile), ("list", keepGoing' listCmd, noCompletion), ("module", keepGoing moduleCmd, completeSetModule), ("main", keepGoing runMain, completeFilename), ("print", keepGoing printCmd, completeExpression), ("quit", quit, noCompletion), ("reload", keepGoing' reloadModule, noCompletion), ("reload!", keepGoing' reloadModuleDefer, 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), ("unadd", keepGoingPaths unAddModule, completeFilename), ("undef", keepGoing undefineMacro, completeMacro), ("unset", keepGoing unsetOptions, completeSetOptions), ("where", keepGoing whereCmd, noCompletion), ("vhdl", keepGoingPaths (makeVHDL opts), completeHomeModuleOrFile), ("verilog", keepGoingPaths (makeVerilog opts), completeHomeModuleOrFile), ("systemverilog", keepGoingPaths (makeSystemVerilog opts), completeHomeModuleOrFile), ("instances", keepGoing' instancesCmd, completeExpression) ] ++ map mkCmdHidden [ -- hidden commands ("all-types", keepGoing' allTypesCmd), ("complete", keepGoing completeCmd), ("loc-at", keepGoing' locAtCmd), ("type-at", keepGoing' typeAtCmd), ("uses", keepGoing' usesCmd) ] where mkCmd (n,a,c) = Command { cmdName = n , cmdAction = a , cmdHidden = False , cmdCompletionFunc = c } mkCmdHidden (n,a) = Command { cmdName = n , cmdAction = a , cmdHidden = True , cmdCompletionFunc = noCompletion } -- 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 = spaces ++ specials ++ symbols symbols, specials, spaces :: String symbols = "!#$%&*+/<=>?@\\^|-~" specials = "(),;[]`{}" spaces = " \t\n" 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" ++ " (!: redefine an existing command name)\n" ++ " :doc display docs for the given name (experimental)\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" ++ " :instances display the class instances available for \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" ++ " (!: defer type errors)\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" ++ " (!: defer type errors)\n" ++ " :run function [ ...] run the function with the given arguments\n" ++ " :script run the script \n" ++ " :type show the type of \n" ++ " :type +d show the type of , defaulting type variables\n" ++ " :type +v show the type of , with its specified tyvars\n" ++ " :unadd ... remove module(s) from the current target set\n" ++ " :undef undefine user-defined command :\n" ++ " :: run the builtin 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 N steps (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 breakpoints\n" ++ " :delete * delete all breakpoints\n" ++ " :disable ... disable the specified breakpoints\n" ++ " :disable * disable all breakpoints\n" ++ " :enable ... enable the specified breakpoints\n" ++ " :enable * enable all breakpoints\n" ++ " :force print , forcing unevaluated parts\n" ++ " :forward [] go forward in the history N step s(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