[project @ 2002-09-06 14:35:42 by simonmar]
[ghc-hetmet.git] / ghc / compiler / ghci / InteractiveUI.hs
index d2a96fc..14208e1 100644 (file)
@@ -1,6 +1,6 @@
 {-# OPTIONS -#include "Linker.h" -#include "SchedAPI.h" #-}
 -----------------------------------------------------------------------------
--- $Id: InteractiveUI.hs,v 1.123 2002/05/01 15:48:48 simonmar Exp $
+-- $Id: InteractiveUI.hs,v 1.133 2002/09/06 14:35:44 simonmar Exp $
 --
 -- GHC Interactive User Interface
 --
@@ -38,7 +38,6 @@ import TyCon          ( tyConName, tyConClass_maybe, isPrimTyCon, DataConDetails(..) )
 import FieldLabel      ( fieldLabelTyCon )
 import SrcLoc          ( isGoodSrcLoc )
 import Module          ( moduleName )
-import NameEnv         ( nameEnvElts )
 import Name            ( Name, isHomePackageName, nameSrcLoc, nameOccName,
                          NamedThing(..) )
 import OccName         ( isSymOcc )
@@ -50,31 +49,35 @@ import Panic                ( GhcException(..), showGhcException )
 import Config
 
 #ifndef mingw32_TARGET_OS
-import Posix
+import System.Posix
 #endif
 
-import Exception
-import Dynamic
 #if HAVE_READLINE_HEADERS && HAVE_READLINE_LIBS
-import Readline 
+import System.Console.Readline as Readline
 #endif
-import Concurrent
-import IOExts
-import SystemExts
+
+--import SystemExts
+
+import Control.Exception as Exception
+import Data.Dynamic
+import Control.Concurrent
 
 import Numeric
-import List
-import System
-import CPUTime
-import Directory
-import IO
-import Char
-import Monad
+import Data.List
+import System.Cmd
+import System.CPUTime
+import System.Environment
+import System.Directory
+import System.IO as IO
+import Data.Char
+import Control.Monad as Monad
 
-import GlaExts         ( unsafeCoerce# )
+import GHC.Exts                ( unsafeCoerce# )
 
 import Foreign         ( nullPtr )
-import CString         ( CString, peekCString, withCString )
+import Foreign.C.String        ( CString, peekCString, withCString )
+import Data.IORef      ( IORef, newIORef, readIORef, writeIORef )
+
 
 -----------------------------------------------------------------------------
 
@@ -164,7 +167,10 @@ interactiveUI cmstate paths cmdline_libs = do
    (cmstate, maybe_hval) 
        <- cmCompileExpr cmstate dflags "IO.hSetBuffering IO.stdout IO.NoBuffering Prelude.>> IO.hSetBuffering IO.stderr IO.NoBuffering"
    case maybe_hval of
-       Just hval -> unsafeCoerce# hval :: IO ()
+       Just hval -> do
+               let action = unsafeCoerce# hval :: IO ()
+               action -- do it now
+               writeIORef turn_off_buffering action -- and save it for later
        _ -> panic "interactiveUI:buffering"
 
    (cmstate, maybe_hval)
@@ -243,8 +249,14 @@ runGHCi paths dflags = do
        loadModule (unwords paths)
 
   -- enter the interactive loop
+#if defined(mingw32_TARGET_OS)
+   -- always show prompt, since hIsTerminalDevice returns True for Consoles
+   -- only, which we may or may not be running under (cf. Emacs sub-shells.)
+  interactiveLoop True
+#else
   is_tty <- io (hIsTerminalDevice stdin)
   interactiveLoop is_tty
+#endif
 
   -- and finally, exit
   io $ do when (verbosity dflags > 0) $ putStrLn "Leaving GHCi."
@@ -262,7 +274,7 @@ interactiveLoop is_tty = do
        then readlineLoop
        else fileLoop stdin False  -- turn off prompt for non-TTY input
 #else
-  fileLoop stdin True
+  fileLoop stdin is_tty
 #endif
 
 
@@ -797,7 +809,7 @@ setProg _ = do
 setOptions wds =
    do -- first, deal with the GHCi opts (+s, +t, etc.)
       let (plus_opts, minus_opts)  = partition isPlus wds
-      mapM setOpt plus_opts
+      mapM_ setOpt plus_opts
 
       -- now, the GHC flags
       pkgs_before <- io (readIORef v_Packages)
@@ -831,7 +843,7 @@ unsetOptions str
          then io (putStrLn ("unknown option: `" ++ head rest2 ++ "'"))
          else do
 
-       mapM unsetOpt plus_opts
+       mapM_ unsetOpt plus_opts
  
        -- can't do GHC flags for now
        if (not (null minus_opts))
@@ -878,6 +890,8 @@ newPackages new_pkgs = do
     new_pkg_info <- getPackageDetails new_pkgs
     mapM_ (linkPackage dflags) (reverse new_pkg_info)
 
+  setContextAfterLoad []
+
 -----------------------------------------------------------------------------
 -- code for `:show'
 
@@ -907,7 +921,7 @@ showBindings = do
        unqual = cmGetPrintUnqual cms
        showBinding b = putStrLn (showSDocForUser unqual (ppr (ifaceTyThing b)))
 
-  io (mapM showBinding (cmGetBindings cms))
+  io (mapM_ showBinding (cmGetBindings cms))
   return ()
 
 -----------------------------------------------------------------------------
@@ -930,6 +944,7 @@ data GHCiOption
 
 GLOBAL_VAR(flush_stdout, error "no flush_stdout", IO ())
 GLOBAL_VAR(flush_stderr, error "no flush_stdout", IO ())
+GLOBAL_VAR(turn_off_buffering, error "no flush_stdout", IO ())
 
 newtype GHCi a = GHCi { unGHCi :: IORef GHCiState -> IO a }
 
@@ -998,6 +1013,9 @@ ghciUnblock (GHCi a) = GHCi $ \s -> Exception.unblock (a s)
 -- directories specified in v_Library_Paths before giving up.
 
 data LibrarySpec = Object FilePath | DLL String
+#ifdef darwin_TARGET_OS
+                   | Framework String
+#endif
 
 -- Packages that don't need loading, because the compiler shares them with
 -- the interpreted program.
@@ -1015,6 +1033,9 @@ loaded_in_ghci
 
 showLS (Object nm)  = "(static) " ++ nm
 showLS (DLL nm) = "(dynamic) " ++ nm
+#ifdef darwin_TARGET_OS
+showLS (Framework nm) = "(framework) " ++ nm
+#endif
 
 linkPackages :: DynFlags -> [LibrarySpec] -> [PackageConfig] -> IO ()
 linkPackages dflags cmdline_lib_specs pkgs
@@ -1076,6 +1097,10 @@ linkPackage dflags pkg
         let dirs      =  library_dirs pkg
         let libs      =  hs_libraries pkg ++ extra_libraries pkg
         classifieds   <- mapM (locateOneObj dirs) libs
+#ifdef darwin_TARGET_OS
+        let fwDirs    =  framework_dirs pkg
+        let frameworks=  extra_frameworks pkg
+#endif
 
         -- Complication: all the .so's must be loaded before any of the .o's.  
        let dlls = [ dll | DLL dll <- classifieds ]
@@ -1086,11 +1111,14 @@ linkPackage dflags pkg
        -- If this package is already part of the GHCi binary, we'll already
        -- have the right DLLs for this package loaded, so don't try to
        -- load them again.
-       when (name pkg `notElem` loaded_in_ghci) $
+       when (name pkg `notElem` loaded_in_ghci) $ do
+#ifdef darwin_TARGET_OS
+           loadFrameworks fwDirs frameworks
+#endif
            loadDynamics dirs dlls
        
        -- After loading all the DLLs, we can load the static objects.
-       mapM loadObj objs
+       mapM_ loadObj objs
 
         maybePutStr dflags "linking ... "
         ok <- resolveObjs
@@ -1104,6 +1132,15 @@ loadDynamics dirs (dll:dlls) = do
     Nothing  -> loadDynamics dirs dlls
     Just err -> throwDyn (CmdLineError ("can't load .so/.DLL for: " 
                                        ++ dll ++ " (" ++ err ++ ")" ))
+#ifdef darwin_TARGET_OS
+loadFrameworks dirs [] = return ()
+loadFrameworks dirs (fw:fws) = do
+  r <- loadFramework dirs fw
+  case r of
+    Nothing  -> loadFrameworks dirs fws
+    Just err -> throwDyn (CmdLineError ("can't load framework: " 
+                                       ++ fw ++ " (" ++ err ++ ")" ))
+#endif
 
 -- Try to find an object file for a given library in the given paths.
 -- If it isn't present, we assume it's a dynamic library.
@@ -1118,7 +1155,7 @@ locateOneObj (d:ds) lib
 -- ----------------------------------------------------------------------------
 -- Loading a dyanmic library (dlopen()-ish on Unix, LoadLibrary-ish on Win32)
 
-#ifdef mingw32_TARGET_OS
+#if defined(mingw32_TARGET_OS) || defined(cygwin32_TARGET_OS)
 loadDynamic paths rootname = addDLL rootname
   -- ignore paths on windows (why? --SDM)
 
@@ -1136,8 +1173,32 @@ loadDynamic [] rootname = do
        -- own builtin paths now.
    addDLL (mkSOName rootname)
 
+#ifdef darwin_TARGET_OS
+mkSOName root = "lib" ++ root ++ ".dylib"
+#else
 mkSOName root = "lib" ++ root ++ ".so"
+#endif
+
+#endif
 
+-- Darwin / MacOS X only: load a framework
+-- a framework is a dynamic library packaged inside a directory of the same
+-- name. They are searched for in different paths than normal libraries.
+#ifdef darwin_TARGET_OS
+loadFramework extraPaths rootname
+   = loadFramework' (extraPaths ++ defaultFrameworkPaths) where
+   defaultFrameworkPaths = ["/Library/Frameworks", "/System/Library/Frameworks"]
+
+   loadFramework' (path:paths) = do
+      let dll = path ++ '/' : rootname ++ ".framework/" ++ rootname
+      b <- doesFileExist dll
+      if not b
+         then loadFramework' paths
+         else addDLL dll
+   loadFramework' [] = do
+       -- tried all our known library paths, but dlopen()
+       -- has no built-in paths for frameworks: give up
+      return $ Just $ "not found"
 #endif
 
 addDLL :: String -> IO (Maybe String)
@@ -1194,4 +1255,12 @@ maybePutStrLn dflags s | verbosity dflags > 0 = putStrLn s
 -----------------------------------------------------------------------------
 -- reverting CAFs
        
-foreign import revertCAFs :: IO ()     -- make it "safe", just in case
+revertCAFs :: IO ()
+revertCAFs = do
+  rts_revertCAFs
+  Monad.join (readIORef turn_off_buffering)
+       -- have to do this again, because we just reverted
+       -- stdout, stderr & stdin to their defaults.
+
+foreign import ccall "revertCAFs" rts_revertCAFs  :: IO ()  
+       -- make it "safe", just in case