Fix #782, #1483, #1649: Unicode GHCi input
[ghc-hetmet.git] / compiler / ghci / InteractiveUI.hs
index 83b5966..a18deb8 100644 (file)
@@ -19,7 +19,7 @@ import Debugger
 import qualified GHC
 import GHC              ( Session, LoadHowMuch(..), Target(..),  TargetId(..),
                           Module, ModuleName, TyThing(..), Phase,
-                          BreakIndex, SrcSpan, Resume, SingleStep )
+                          BreakIndex, SrcSpan, Resume, SingleStep, Id )
 import PprTyThing
 import DynFlags
 
@@ -47,12 +47,12 @@ import Util
 import NameSet
 import Maybes          ( orElse )
 import FastString
+import Encoding
 
 #ifndef mingw32_HOST_OS
 import System.Posix hiding (getEnv)
 #else
 import GHC.ConsoleHandler ( flushConsole )
-import System.Win32      ( setConsoleCP, setConsoleOutputCP )
 import qualified System.Win32
 #endif
 
@@ -75,14 +75,13 @@ import System.Exit  ( exitWith, ExitCode(..) )
 import System.Directory
 import System.IO
 import System.IO.Error as IO
-import System.IO.Unsafe
 import Data.Char
 import Data.Dynamic
 import Data.Array
 import Control.Monad as Monad
 import Text.Printf
-
-import Foreign.StablePtr       ( newStablePtr )
+import Foreign
+import Foreign.C        ( withCStringLen )
 import GHC.Exts                ( unsafeCoerce# )
 import GHC.IOBase      ( IOErrorType(InvalidArgument) )
 
@@ -339,7 +338,7 @@ runGHCi paths maybe_expr = do
          either_hdl <- io (IO.try (openFile "./.ghci" ReadMode))
          case either_hdl of
             Left _e   -> return ()
-            Right hdl -> runCommands (fileLoop hdl False)
+            Right hdl -> runCommands (fileLoop hdl False False)
     
   when (read_dot_files) $ do
     -- Read in $HOME/.ghci
@@ -355,7 +354,7 @@ runGHCi paths maybe_expr = do
               either_hdl <- io (IO.try (openFile file ReadMode))
               case either_hdl of
                  Left _e   -> return ()
-                 Right hdl -> runCommands (fileLoop hdl False)
+                 Right hdl -> runCommands (fileLoop hdl False False)
 
   -- Perform a :load for files given on the GHCi command line
   -- When in -e mode, if the load fails then we want to stop
@@ -386,9 +385,6 @@ runGHCi paths maybe_expr = do
                       | otherwise -> io (ioError err)
              Right () -> return ()
 #endif
-            -- initialise the console if necessary
-            io setUpConsole
-
             -- enter the interactive loop
             interactiveLoop is_tty show_prompt
         Just expr -> do
@@ -418,9 +414,9 @@ interactiveLoop is_tty show_prompt =
 #ifdef USE_READLINE
   if (is_tty) 
        then runCommands readlineLoop
-       else runCommands (fileLoop stdin show_prompt)
+       else runCommands (fileLoop stdin show_prompt is_tty)
 #else
-  runCommands (fileLoop stdin show_prompt)
+  runCommands (fileLoop stdin show_prompt is_tty)
 #endif
 
 
@@ -456,8 +452,8 @@ checkPerms name =
          else return True
 #endif
 
-fileLoop :: Handle -> Bool -> GHCi (Maybe String)
-fileLoop hdl show_prompt = do
+fileLoop :: Handle -> Bool -> Bool -> GHCi (Maybe String)
+fileLoop hdl show_prompt is_tty = do
    when show_prompt $ do
         prompt <- mkPrompt
         (io (putStr prompt))
@@ -471,7 +467,33 @@ fileLoop hdl show_prompt = do
                 -- this can happen if the user closed stdin, or
                 -- perhaps did getContents which closes stdin at
                 -- EOF.
-        Right l -> return (Just l)
+        Right l -> do
+                   str <- io $ consoleInputToUnicode is_tty l
+                   return (Just str)
+
+#ifdef mingw32_HOST_OS
+-- Convert the console input into Unicode according to the current code page.
+-- The Windows console stores Unicode characters directly, so this is a
+-- rather roundabout way of doing things... oh well.
+-- See #782, #1483, #1649
+consoleInputToUnicode :: Bool -> String -> IO String
+consoleInputToUnicode is_tty str
+  | is_tty = do
+    cp <- System.Win32.getConsoleCP
+    System.Win32.stringToUnicode cp str
+  | otherwise =
+    decodeStringAsUTF8 str
+#else
+-- for Unix, assume the input is in UTF-8 and decode it to a Unicode String. 
+-- See #782.
+consoleInputToUnicode :: Bool -> String -> IO String
+consoleInputToUnicode _is_tty str = decodeStringAsUTF8 str
+#endif
+
+decodeStringAsUTF8 :: String -> IO String
+decodeStringAsUTF8 str =
+  withCStringLen str $ \(cstr,len) -> 
+    utf8DecodeString (castPtr cstr :: Ptr Word8) len
 
 mkPrompt :: GHCi String
 mkPrompt = do
@@ -524,7 +546,8 @@ readlineLoop = do
         Nothing -> return Nothing
         Just l  -> do
                    io (addHistory l)
-                   return (Just l)
+                   str <- io $ consoleInputToUnicode True l
+                   return (Just str)
 #endif
 
 queryQueue :: GHCi (Maybe String)
@@ -631,7 +654,11 @@ afterRunStmt step_here run_result = do
                printForUser $ ptext SLIT("Stopped at") <+> 
                        ppr (GHC.resumeSpan $ head resumes)
 --               printTypeOfNames session names
-               printTypeAndContentOfNames session names
+               let namesSorted = sortBy compareNames names
+               tythings <- catMaybes `liftM` 
+                              io (mapM (GHC.lookupName session) namesSorted)
+
+               printTypeAndContents session [id | AnId id <- tythings]
                maybe (return ()) runBreakCmd mb_info
                -- run the command set with ":set stop <cmd>"
                st <- getGHCiState
@@ -648,19 +675,6 @@ afterRunStmt step_here run_result = do
 
   return (case run_result of GHC.RunOk _ -> True; _ -> False)
 
-      where printTypeAndContentOfNames session names = do
-              let namesSorted = sortBy compareNames names
-              tythings <- catMaybes `liftM` 
-                              io (mapM (GHC.lookupName session) namesSorted)
-             let ids = [id | AnId id <- tythings]
-              terms <- mapM (io . GHC.obtainTermB session 10 False) ids
-              docs_terms <- mapM (io . showTerm session) terms                                   
-             dflags <- getDynFlags
-             let pefas = dopt Opt_PrintExplicitForalls dflags
-              printForUser $ vcat $ zipWith (\ty cts -> ty <+> equals <+> cts)
-                                            (map (pprTyThing pefas . AnId) ids)
-                                            docs_terms
-
 runBreakCmd :: GHC.BreakInfo -> GHCi ()
 runBreakCmd info = do
   let mod = GHC.breakInfo_module info
@@ -688,6 +702,22 @@ printTypeOfName session n
             Nothing    -> return ()
             Just thing -> printTyThing thing
 
+printTypeAndContents :: Session -> [Id] -> GHCi ()
+printTypeAndContents session ids = do
+  dflags <- getDynFlags
+  let pefas     = dopt Opt_PrintExplicitForalls dflags
+      pcontents = dopt Opt_PrintBindContents dflags
+  if pcontents 
+    then do
+      let depthBound = 100
+      terms      <- mapM (io . GHC.obtainTermB session depthBound False) ids
+      docs_terms <- mapM (io . showTerm session) terms
+      printForUser $ vcat $ zipWith (\ty cts -> ty <+> equals <+> cts)
+                                    (map (pprTyThing pefas . AnId) ids)
+                                    docs_terms
+    else printForUser $ vcat $ map (pprTyThing pefas . AnId) ids
+
+
 specialCommand :: String -> GHCi Bool
 specialCommand ('!':str) = shellEscape (dropWhile isSpace str)
 specialCommand str = do
@@ -798,7 +828,7 @@ addModule files = do
   session <- getSession
   io (mapM_ (GHC.addTarget session) targets)
   ok <- io (GHC.load session LoadAllTargets)
-  afterLoad ok session
+  afterLoad ok session Nothing
 
 changeDirectory :: String -> GHCi ()
 changeDirectory dir = do
@@ -941,7 +971,7 @@ loadModule' files = do
   -- as a ToDo for now.
 
   io (GHC.setTargets session targets)
-  doLoad session LoadAllTargets
+  doLoad session False LoadAllTargets
 
 checkModule :: String -> GHCi ()
 checkModule m = do
@@ -959,30 +989,43 @@ checkModule m = do
                        (text "global names: " <+> ppr global) $$
                        (text "local  names: " <+> ppr local)
           _ -> empty))
-  afterLoad (successIf (isJust result)) session
+  afterLoad (successIf (isJust result)) session Nothing
 
 reloadModule :: String -> GHCi ()
 reloadModule m = do
   session <- getSession
-  doLoad session $ if null m then LoadAllTargets 
-                             else LoadUpTo (GHC.mkModuleName m)
+  doLoad session True $ if null m then LoadAllTargets 
+                                  else LoadUpTo (GHC.mkModuleName m)
   return ()
 
-doLoad :: Session -> LoadHowMuch -> GHCi SuccessFlag
-doLoad session howmuch = do
+doLoad :: Session -> Bool -> LoadHowMuch -> GHCi SuccessFlag
+doLoad session retain_context howmuch = do
   -- turn off breakpoints before we load: we can't turn them off later, because
   -- the ModBreaks will have gone away.
   discardActiveBreakPoints
+  context <- io $ GHC.getContext session
   ok <- io (GHC.load session howmuch)
-  afterLoad ok session
+  afterLoad ok session (if retain_context then Just context else Nothing)
   return ok
 
-afterLoad :: SuccessFlag -> Session -> GHCi ()
-afterLoad ok session = do
+afterLoad :: SuccessFlag -> Session -> Maybe ([Module],[Module]) -> GHCi ()
+afterLoad ok session maybe_context = do
   io (revertCAFs)  -- always revert CAFs on load.
   discardTickArrays
   loaded_mods <- getLoadedModules session
-  setContextAfterLoad session loaded_mods
+
+  -- try to retain the old module context for :reload.  This might
+  -- not be possible, for example if some modules have gone away, so
+  -- we attempt to set the same context, backing off to the default
+  -- context if that fails.
+  case maybe_context of
+     Nothing -> setContextAfterLoad session loaded_mods
+     Just (as,bs) -> do
+        r <- io $ Exception.try (GHC.setContext session as bs)
+        case r of
+           Left _err -> setContextAfterLoad session loaded_mods
+           Right _   -> return ()
+
   modulesLoadedMsg ok (map GHC.ms_mod_name loaded_mods)
 
 setContextAfterLoad :: Session -> [GHC.ModSummary] -> GHCi ()
@@ -1184,14 +1227,10 @@ separate :: Session -> [String] -> [Module] -> [Module]
         -> GHCi ([Module],[Module])
 separate _       []             as bs = return (as,bs)
 separate session (('*':str):ms) as bs = do
-   m <- io $ GHC.findModule session (GHC.mkModuleName str) Nothing
-   b <- io $ GHC.moduleIsInterpreted session m
-   if b then separate session ms (m:as) bs
-       else throwDyn (CmdLineError ("module '"
-                        ++ GHC.moduleNameString (GHC.moduleName m)
-                        ++ "' is not interpreted"))
+  m <- wantInterpretedModule str
+  separate session ms (m:as) bs
 separate session (str:ms) as bs = do
-  m <- io $ GHC.findModule session (GHC.mkModuleName str) Nothing
+  m <- lookupModule str
   separate session ms as (m:bs)
 
 newContext :: [String] -> GHCi ()
@@ -1444,8 +1483,7 @@ showBindings :: GHCi ()
 showBindings = do
   s <- getSession
   bindings <- io (GHC.getBindings s)
-  mapM_ printTyThing $ sortBy compareTyThings bindings
-  return ()
+  printTypeAndContents s [ id | AnId id <- sortBy compareTyThings bindings]
 
 compareTyThings :: TyThing -> TyThing -> Ordering
 t1 `compareTyThings` t2 = getName t1 `compareNames` getName t2
@@ -1700,33 +1738,6 @@ wantNameFromInterpretedModule noCanDo str and_then = do
                                 text " is not interpreted"
                else and_then n
 
--- ----------------------------------------------------------------------------
--- Windows console setup
-
-setUpConsole :: IO ()
-setUpConsole = do
-#ifdef mingw32_HOST_OS
-       -- On Windows we need to set a known code page, otherwise the characters
-       -- we read from the console will be be in some strange encoding, and
-       -- similarly for characters we write to the console.
-       --
-       -- At the moment, GHCi pretends all input is Latin-1.  In the
-       -- future we should support UTF-8, but for now we set the code
-       -- pages to Latin-1.  Doing it this way does lead to problems,
-       -- however: see bug #1649.
-       --
-       -- It seems you have to set the font in the console window to
-       -- a Unicode font in order for output to work properly,
-       -- otherwise non-ASCII characters are mapped wrongly.  sigh.
-       -- (see MSDN for SetConsoleOutputCP()).
-       --
-        -- This call has been known to hang on some machines, see bug #1483
-        --
-       setConsoleCP 28591       -- ISO Latin-1
-       setConsoleOutputCP 28591 -- ISO Latin-1
-#endif
-       return ()
-
 -- -----------------------------------------------------------------------------
 -- commands for debugger