re-fix of #1205, fix #2542
authorSimon Marlow <marlowsd@gmail.com>
Wed, 27 Aug 2008 10:24:14 +0000 (10:24 +0000)
committerSimon Marlow <marlowsd@gmail.com>
Wed, 27 Aug 2008 10:24:14 +0000 (10:24 +0000)
New form of :load in GHCi:

> :load *A

forces A to be loaded as byte-code.  See the manual for details.  The
previous behaviour for specifying filenames vs. module names on the
command line and in :load has been restored.

The Target datatype has a new Bool field, which is True if the target
is allowed to be loaded from compiled code, or False otherwise, so
this functionality is available via the GHC API.  guessTarget
understands the *-prefix form for specifying targets.

compiler/ghci/InteractiveUI.hs
compiler/main/GHC.hs
compiler/main/HscTypes.lhs
docs/users_guide/ghci.xml

index 48033ae..f5debfe 100644 (file)
@@ -199,7 +199,7 @@ helpText =
  "   <statement>                 evaluate/run <statement>\n" ++
  "   :                           repeat last command\n" ++
  "   :{\\n ..lines.. \\n:}\\n       multiline command\n" ++
- "   :add <filename> ...         add module(s) to the current target set\n" ++
+ "   :add [*]<module> ...        add module(s) to the current target set\n" ++
  "   :browse[!] [[*]<mod>]       display the names defined by module <mod>\n" ++
  "                               (!: more details; *: all top-level names)\n" ++
  "   :cd <dir>                   change directory to <dir>\n" ++
@@ -212,7 +212,7 @@ helpText =
  "   :help, :?                   display this list of commands\n" ++
  "   :info [<name> ...]          display information about the given names\n" ++
  "   :kind <type>                show the kind of <type>\n" ++
- "   :load <filename> ...        load module(s) and their dependents\n" ++
+ "   :load [*]<module> ...       load module(s) and their dependents\n" ++
  "   :main [<arguments> ...]     run the main function with the given arguments\n" ++
  "   :module [+/-] [*]<mod> ...  set the context for expression evaluation\n" ++
  "   :quit                       exit GHCi\n" ++
@@ -916,9 +916,11 @@ addModule files = do
   files <- mapM expandPath files
   targets <- mapM (\m -> io (GHC.guessTarget m Nothing)) files
   session <- getSession
-  io (mapM_ (GHC.addTarget session) targets)
+  -- remove old targets with the same id; e.g. for :add *M
+  io $ mapM_ (GHC.removeTarget session) [ tid | Target tid _ _ <- targets ]
+  io $ mapM_ (GHC.addTarget session) targets
   prev_context <- io $ GHC.getContext session
-  ok <- io (GHC.load session LoadAllTargets)
+  ok <- io $ GHC.load session LoadAllTargets
   afterLoad ok session False prev_context
 
 changeDirectory :: String -> GHCi ()
@@ -981,7 +983,7 @@ chooseEditFile =
               Just file -> return file
               Nothing   -> ghcError (CmdLineError "No files to edit.")
           
-  where fromTarget (GHC.Target (GHC.TargetFile f _) _) = Just f
+  where fromTarget (GHC.Target (GHC.TargetFile f _) _ _) = Just f
         fromTarget _ = Nothing -- when would we get a module target?
 
 defineMacro :: Bool{-overwrite-} -> String -> GHCi ()
@@ -1141,9 +1143,9 @@ setContextAfterLoad session prev keep_ctxt ms = do
        []    -> Nothing
        (m:_) -> Just m
 
-   summary `matches` Target (TargetModule m) _
+   summary `matches` Target (TargetModule m) _ _
        = GHC.ms_mod_name summary == m
-   summary `matches` Target (TargetFile f _) _ 
+   summary `matches` Target (TargetFile f _) _ _ 
        | Just f' <- GHC.ml_hs_file (GHC.ms_location summary)   = f == f'
    _ `matches` _
        = False
@@ -1890,9 +1892,12 @@ wantInterpretedModule :: String -> GHCi Module
 wantInterpretedModule str = do
    session <- getSession
    modl <- lookupModule str
+   dflags <- getDynFlags
+   when (GHC.modulePackageId modl /= thisPackage dflags) $
+      ghcError (CmdLineError ("module '" ++ str ++ "' is from another package;\nthis command requires an interpreted module"))
    is_interpreted <- io (GHC.moduleIsInterpreted session modl)
    when (not is_interpreted) $
-       ghcError (CmdLineError ("module '" ++ str ++ "' is not interpreted"))
+       ghcError (CmdLineError ("module '" ++ str ++ "' is not interpreted; try \':add *" ++ str ++ "' first"))
    return modl
 
 wantNameFromInterpretedModule :: (Name -> SDoc -> GHCi ()) -> String
index 7ecc194..b29912e 100644 (file)
@@ -463,7 +463,7 @@ removeTarget :: Session -> TargetId -> IO ()
 removeTarget s target_id
   = modifySession s (\h -> h{ hsc_targets = filter (hsc_targets h) })
   where
-   filter targets = [ t | t@(Target id _) <- targets, id /= target_id ]
+   filter targets = [ t | t@(Target id _ _) <- targets, id /= target_id ]
 
 -- Attempts to guess what Target a string refers to.  This function implements
 -- the --make/GHCi command-line syntax for filenames: 
@@ -475,30 +475,37 @@ removeTarget s target_id
 --     - otherwise interpret the string as a module name
 --
 guessTarget :: String -> Maybe Phase -> IO Target
-guessTarget file (Just phase)
-   = return (Target (TargetFile file (Just phase)) Nothing)
-guessTarget file Nothing
+guessTarget str (Just phase)
+   = return (Target (TargetFile str (Just phase)) True Nothing)
+guessTarget str Nothing
    | isHaskellSrcFilename file
-   = return (Target (TargetFile file Nothing) Nothing)
-   | looksLikeModuleName file
-   = return (Target (TargetModule (mkModuleName file)) Nothing)
+   = return (target (TargetFile file Nothing))
    | otherwise
    = do exists <- doesFileExist hs_file
        if exists
-          then return (Target (TargetFile hs_file Nothing) Nothing)
+          then return (target (TargetFile hs_file Nothing))
           else do
        exists <- doesFileExist lhs_file
        if exists
-          then return (Target (TargetFile lhs_file Nothing) Nothing)
+          then return (target (TargetFile lhs_file Nothing))
           else do
+        if looksLikeModuleName file
+           then return (target (TargetModule (mkModuleName file)))
+           else do
         throwGhcException
                  (ProgramError (showSDoc $
                  text "target" <+> quotes (text file) <+> 
                  text "is not a module name or a source file"))
      where 
+         (file,obj_allowed)
+                | '*':rest <- str = (rest, False)
+                | otherwise       = (str,  True)
+
         hs_file  = file <.> "hs"
         lhs_file = file <.> "lhs"
 
+         target tid = Target tid obj_allowed Nothing
+
 -- -----------------------------------------------------------------------------
 -- Extending the program scope
 
@@ -1705,15 +1712,17 @@ downsweep hsc_env old_summaries excl_mods allow_dup_roots
        old_summary_map = mkNodeMap old_summaries
 
        getRootSummary :: Target -> IO ModSummary
-       getRootSummary (Target (TargetFile file mb_phase) maybe_buf)
+       getRootSummary (Target (TargetFile file mb_phase) obj_allowed maybe_buf)
           = do exists <- doesFileExist file
                if exists 
-                   then summariseFile hsc_env old_summaries file mb_phase maybe_buf
+                   then summariseFile hsc_env old_summaries file mb_phase 
+                                       obj_allowed maybe_buf
                    else throwErrMsg $ mkPlainErrMsg noSrcSpan $
                           text "can't find file:" <+> text file
-       getRootSummary (Target (TargetModule modl) maybe_buf)
+       getRootSummary (Target (TargetModule modl) obj_allowed maybe_buf)
           = do maybe_summary <- summariseModule hsc_env old_summary_map False 
-                                          (L rootLoc modl) maybe_buf excl_mods
+                                          (L rootLoc modl) obj_allowed 
+                                           maybe_buf excl_mods
                case maybe_summary of
                   Nothing -> packageModErr modl
                   Just s  -> return s
@@ -1749,12 +1758,13 @@ downsweep hsc_env old_summaries excl_mods allow_dup_roots
                loop ss done
            else
                do { multiRootsErr summs; return [] }
-         | otherwise         = do { mb_s <- summariseModule hsc_env old_summary_map 
-                                                is_boot wanted_mod Nothing excl_mods
-                                  ; case mb_s of
-                                       Nothing -> loop ss done
-                                       Just s  -> loop (msDeps s ++ ss) 
-                                                       (addToFM done key [s]) }
+         | otherwise
+          = do mb_s <- summariseModule hsc_env old_summary_map 
+                                       is_boot wanted_mod True
+                                       Nothing excl_mods
+               case mb_s of
+                   Nothing -> loop ss done
+                   Just s  -> loop (msDeps s ++ ss) (addToFM done key [s])
          where
            key = (unLoc wanted_mod, if is_boot then HsBootFile else HsSrcFile)
 
@@ -1793,10 +1803,11 @@ summariseFile
        -> [ModSummary]                 -- old summaries
        -> FilePath                     -- source file name
        -> Maybe Phase                  -- start phase
+        -> Bool                         -- object code allowed?
        -> Maybe (StringBuffer,ClockTime)
        -> IO ModSummary
 
-summariseFile hsc_env old_summaries file mb_phase maybe_buf
+summariseFile hsc_env old_summaries file mb_phase obj_allowed maybe_buf
        -- we can use a cached summary if one is available and the
        -- source file hasn't changed,  But we have to look up the summary
        -- by source file, rather than module name as we do in summarise.
@@ -1816,7 +1827,8 @@ summariseFile hsc_env old_summaries file mb_phase maybe_buf
        if ms_hs_date old_summary == src_timestamp 
           then do -- update the object-file timestamp
                  obj_timestamp <-
-                    if isObjectTarget (hscTarget (hsc_dflags hsc_env)) -- bug #1205
+                    if isObjectTarget (hscTarget (hsc_dflags hsc_env)) 
+                        || obj_allowed -- bug #1205
                         then getObjTimestamp location False
                         else return Nothing
                  return old_summary{ ms_obj_date = obj_timestamp }
@@ -1849,7 +1861,8 @@ summariseFile hsc_env old_summaries file mb_phase maybe_buf
         -- when the user asks to load a source file by name, we only
         -- use an object file if -fobject-code is on.  See #1205.
        obj_timestamp <-
-            if isObjectTarget (hscTarget (hsc_dflags hsc_env))
+            if isObjectTarget (hscTarget (hsc_dflags hsc_env)) 
+               || obj_allowed -- bug #1205
                 then modificationTimeIfExists (ml_obj_file location)
                 else return Nothing
 
@@ -1875,11 +1888,13 @@ summariseModule
          -> NodeMap ModSummary -- Map of old summaries
          -> IsBootInterface    -- True <=> a {-# SOURCE #-} import
          -> Located ModuleName -- Imported module to be summarised
+          -> Bool               -- object code allowed?
          -> Maybe (StringBuffer, ClockTime)
          -> [ModuleName]               -- Modules to exclude
          -> IO (Maybe ModSummary)      -- Its new summary
 
-summariseModule hsc_env old_summary_map is_boot (L loc wanted_mod) maybe_buf excl_mods
+summariseModule hsc_env old_summary_map is_boot (L loc wanted_mod) 
+                obj_allowed maybe_buf excl_mods
   | wanted_mod `elem` excl_mods
   = return Nothing
 
@@ -1910,7 +1925,11 @@ summariseModule hsc_env old_summary_map is_boot (L loc wanted_mod) maybe_buf exc
     check_timestamp old_summary location src_fn src_timestamp
        | ms_hs_date old_summary == src_timestamp = do
                -- update the object-file timestamp
-               obj_timestamp <- getObjTimestamp location is_boot
+                obj_timestamp <- 
+                    if isObjectTarget (hscTarget (hsc_dflags hsc_env)) 
+                       || obj_allowed -- bug #1205
+                       then getObjTimestamp location is_boot
+                       else return Nothing
                return (Just old_summary{ ms_obj_date = obj_timestamp })
        | otherwise = 
                -- source changed: re-summarise.
@@ -1965,7 +1984,12 @@ summariseModule hsc_env old_summary_map is_boot (L loc wanted_mod) maybe_buf exc
                               $$ text "Expected:" <+> quotes (ppr wanted_mod)
 
                -- Find the object timestamp, and return the summary
-       obj_timestamp <- getObjTimestamp location is_boot
+             
+       obj_timestamp <-
+           if isObjectTarget (hscTarget (hsc_dflags hsc_env)) 
+              || obj_allowed -- bug #1205
+              then getObjTimestamp location is_boot
+              else return Nothing
 
        return (Just ( ModSummary { ms_mod       = mod, 
                                    ms_hsc_src   = hsc_src,
index 7909238..d5077fe 100644 (file)
@@ -255,7 +255,10 @@ hscEPS hsc_env = readIORef (hsc_EPS hsc_env)
 -- module.  If so, use this instead of the file contents (this
 -- is for use in an IDE where the file hasn't been saved by
 -- the user yet).
-data Target = Target TargetId (Maybe (StringBuffer,ClockTime))
+data Target = Target
+      TargetId                          -- module or filename
+      Bool                              -- object code allowed?
+      (Maybe (StringBuffer,ClockTime))  -- in-memory text buffer?
 
 data TargetId
   = TargetModule ModuleName
@@ -268,7 +271,8 @@ data TargetId
   deriving Eq
 
 pprTarget :: Target -> SDoc
-pprTarget (Target id _) = pprTargetId id
+pprTarget (Target id obj _) = 
+   (if obj then char '*' else empty) <> pprTargetId id
 
 instance Outputable Target where
     ppr = pprTarget
index 1f20df4..402c7cb 100644 (file)
@@ -302,12 +302,29 @@ Ok, modules loaded: A, B, C, D.
     confusion, because non-exported top-level definitions of a module
     are only available for use in expressions at the prompt when the
     module is interpreted (see <xref linkend="ghci-scope" />).  For
-    this reason, if you ask GHCi to load a filename rather than a
-    module name (e.g. <literal>:load Main.hs</literal> rather than
-    <literal>:load Main</literal>) then any existing object file will
-    be ignored and the module will be interpreted rather than
-    compiled.  Using <literal>-fobject-code</literal> disables this
-    behaviour (see <xref linkend="ghci-obj" />).</para>
+    this reason, you might sometimes want to force GHCi to load a
+    module using the interpreter.  This can be done by prefixing
+      a <literal>*</literal> to the module name or filename when
+      using <literal>:load</literal>, for example</para>
+
+<screen>
+Prelude> :load *A
+Compiling A                ( A.hs, interpreted )
+*A>
+</screen>
+
+<para>When the <literal>*</literal> is used, GHCi ignores any
+  pre-compiled object code and interprets the module.  If you have
+  already loaded a number of modules as object code and decide that
+  you wanted to interpret one of them, instead of re-loading the whole
+  set you can use <literal>:add *M</literal> to specify that you want
+  <literal>M</literal> to be interpreted (note that this might cause
+  other modules to be interpreted too, because compiled modules cannot
+  depend on interpreted ones).</para>
+
+<para>To always compile everything to object code and never use the
+  interpreter, use the <literal>-fobject-code</literal> option (see
+  <xref linkend="ghci-obj" />).</para>
 
     <para>HINT: since GHCi will only use a compiled object file if it
     can be sure that the compiled version is up-to-date, a good technique
@@ -552,9 +569,9 @@ Compiling Main             ( Main.hs, interpreted )
       <para>NOTE: for technical reasons, GHCi can only support the
       <literal>*</literal>-form for modules that are interpreted.
       Compiled modules and package modules can only contribute their
-      exports to the current scope.  This is why GHCi will always
-      interpret, not compile, a module if you specify its filename
-      rather than its module name to <literal>:load</literal>.</para>
+      exports to the current scope.  To ensure that GHCi loads the
+      interpreted version of a module, add the <literal>*</literal>
+      when loading the module, e.g. <literal>:load *M</literal>.</para>
 
       <para>The scope is manipulated using the
       <literal>:module</literal> command.  For example, if the current
@@ -1477,7 +1494,7 @@ a :: a
 <screen>
 *Main> :set -fbreak-on-exception
 *Main> :trace qsort ("abc" ++ undefined)
-"Stopped at &lt;exception thrown&gt;
+&ldquo;Stopped at &lt;exception thrown&gt;
 _exception :: e
 [&lt;exception thrown&gt;] *Main&gt; :hist
 -1  : qsort.hs:3:24-38
@@ -1762,13 +1779,16 @@ $ ghci -lm
 
       <varlistentry>
        <term>
-          <literal>:add</literal> <replaceable>module</replaceable> ...
+          <literal>:add</literal> <optional><literal>*</literal></optional><replaceable>module</replaceable> ...
           <indexterm><primary><literal>:add</literal></primary></indexterm>
         </term>
        <listitem>
          <para>Add <replaceable>module</replaceable>(s) to the
          current <firstterm>target set</firstterm>, and perform a
-         reload.</para>
+         reload.  Normally pre-compiled code for the module will be
+         loaded if available, or otherwise the module will be
+         compiled to byte-code.  Using the <literal>*</literal>
+         prefix forces the module to be loaded as byte-code.</para>
        </listitem>
       </varlistentry>
 
@@ -2139,7 +2159,7 @@ Prelude> :. cmds.ghci
 
       <varlistentry>
        <term>
-          <literal>:load</literal> <replaceable>module</replaceable> ...
+          <literal>:load</literal> <optional><literal>*</literal></optional><replaceable>module</replaceable> ...
           <indexterm><primary><literal>:load</literal></primary></indexterm>
         </term>
        <listitem>
@@ -2156,6 +2176,11 @@ Prelude> :. cmds.ghci
          to unload all the currently loaded modules and
          bindings.</para>
 
+          <para>Normally pre-compiled code for a module will be loaded
+         if available, or otherwise the module will be compiled to
+         byte-code.  Using the <literal>*</literal> prefix forces a
+         module to be loaded as byte-code.</para>
+
          <para>After a <literal>:load</literal> command, the current
          context is set to:</para>