[project @ 2002-08-29 15:44:11 by simonmar]
[ghc-hetmet.git] / ghc / compiler / ghci / InteractiveUI.hs
index 8d3bd96..4825368 100644 (file)
@@ -1,13 +1,17 @@
 {-# OPTIONS -#include "Linker.h" -#include "SchedAPI.h" #-}
 -----------------------------------------------------------------------------
--- $Id: InteractiveUI.hs,v 1.121 2002/04/24 09:42:18 simonmar Exp $
+-- $Id: InteractiveUI.hs,v 1.132 2002/08/29 15:44:14 simonmar Exp $
 --
 -- GHC Interactive User Interface
 --
 -- (c) The GHC Team 2000
 --
 -----------------------------------------------------------------------------
-module InteractiveUI ( interactiveUI, ghciWelcomeMsg ) where
+module InteractiveUI ( 
+       interactiveUI,  -- :: CmState -> [FilePath] -> [LibrarySpec] -> IO ()
+       LibrarySpec(..),
+       ghciWelcomeMsg
+   ) where
 
 #include "../includes/config.h"
 #include "HsVersions.h"
@@ -34,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 )
@@ -49,28 +52,32 @@ import Config
 import Posix
 #endif
 
-import Exception
-import Dynamic
 #if HAVE_READLINE_HEADERS && HAVE_READLINE_LIBS
 import 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         ( peekCString )
+import Foreign.C.String        ( CString, peekCString, withCString )
+import Data.IORef      ( IORef, newIORef, readIORef, writeIORef )
+
 
 -----------------------------------------------------------------------------
 
@@ -160,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)
@@ -239,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."
@@ -258,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
 
 
@@ -793,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)
@@ -827,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))
@@ -874,6 +890,8 @@ newPackages new_pkgs = do
     new_pkg_info <- getPackageDetails new_pkgs
     mapM_ (linkPackage dflags) (reverse new_pkg_info)
 
+  setContextAfterLoad []
+
 -----------------------------------------------------------------------------
 -- code for `:show'
 
@@ -903,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 ()
 
 -----------------------------------------------------------------------------
@@ -926,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 }
 
@@ -993,11 +1012,30 @@ ghciUnblock (GHCi a) = GHCi $ \s -> Exception.unblock (a s)
 -- For dynamic objects only, try to find the object file in all the 
 -- directories specified in v_Library_Paths before giving up.
 
-type LibrarySpec
-   = Either FilePath String
+data LibrarySpec = Object FilePath | DLL String
+#ifdef darwin_TARGET_OS
+                   | Framework String
+#endif
 
-showLS (Left nm)  = "(static) " ++ nm
-showLS (Right nm) = "(dynamic) " ++ nm
+-- Packages that don't need loading, because the compiler shares them with
+-- the interpreted program.
+dont_load_these = [ "rts" ]
+
+-- Packages that are already linked into GHCi.  For mingw32, we only
+-- skip gmp and rts, since std and after need to load the msvcrt.dll
+-- library which std depends on.
+loaded_in_ghci
+#          ifndef mingw32_TARGET_OS
+           = [ "std", "concurrent", "posix", "text", "util" ]
+#          else
+          = [ ]
+#          endif
+
+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
@@ -1007,6 +1045,7 @@ linkPackages dflags cmdline_lib_specs pkgs
        if (null cmdline_lib_specs)
           then return ()
           else do maybePutStr dflags "final link ... "
+
                   ok <- resolveObjs
                   if ok then maybePutStrLn dflags "done."
                         else throwDyn (InstallationError 
@@ -1016,15 +1055,15 @@ linkPackages dflags cmdline_lib_specs pkgs
         preloadLib dflags lib_paths lib_spec
            = do maybePutStr dflags ("Loading object " ++ showLS lib_spec ++ " ... ")
                 case lib_spec of
-                   Left static_ish
+                   Object static_ish
                       -> do b <- preload_static lib_paths static_ish
                             maybePutStrLn dflags (if b  then "done." 
                                                        else "not found")
-                   Right dll_unadorned
+                   DLL dll_unadorned
                       -> -- We add "" to the set of paths to try, so that
                          -- if none of the real paths match, we force addDLL
                          -- to look in the default dynamic-link search paths.
-                         do maybe_errstr <- preload_dynamic (lib_paths++[""]) 
+                         do maybe_errstr <- loadDynamic (lib_paths++[""]) 
                                                             dll_unadorned
                             case maybe_errstr of
                                Nothing -> return ()
@@ -1046,80 +1085,132 @@ linkPackages dflags cmdline_lib_specs pkgs
                 if not b then return False
                          else loadObj name >> return True
 
-        -- return Nothing == success, else Just error message from addDLL
-        preload_dynamic [] name
-           = return Nothing
-        preload_dynamic (path:paths) rootname
-           = do -- addDLL returns NULL on success
-                maybe_errmsg <- addDLL path rootname
-                if    maybe_errmsg == nullPtr
-                 then preload_dynamic paths rootname
-                 else do str <- peekCString maybe_errmsg
-                         return (Just str)
-
         give_up 
            = (throwDyn . CmdLineError)
                 "user specified .o/.so/.DLL could not be loaded."
 
--- Packages that don't need loading, because the compiler shares them with
--- the interpreted program.
-dont_load_these = [ "rts" ]
-
--- Packages that are already linked into GHCi.  For mingw32, we only
--- skip gmp and rts, since std and after need to load the msvcrt.dll
--- library which std depends on.
-loaded_in_ghci
-#          ifndef mingw32_TARGET_OS
-           = [ "std", "concurrent", "posix", "text", "util" ]
-#          else
-          = [ ]
-#          endif
-
 linkPackage :: DynFlags -> PackageConfig -> IO ()
 linkPackage dflags pkg
    | name pkg `elem` dont_load_these = return ()
    | otherwise
    = do 
-        -- For each obj, try obj.o and if that fails, obj.so.
-        -- Complication: all the .so's must be loaded before any of the .o's.  
         let dirs      =  library_dirs pkg
-        let objs      =  hs_libraries pkg ++ extra_libraries pkg
-        classifieds   <- mapM (locateOneObj dirs) objs
+        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
 
-       -- Don't load the .so libs if this is a package GHCi is already
-       -- linked against, because we'll already have the .so linked in.
-       let (so_libs, obj_libs) = partition isRight classifieds
-        let sos_first | name pkg `elem` loaded_in_ghci = obj_libs
-                     | otherwise                      = so_libs ++ obj_libs
+        -- Complication: all the .so's must be loaded before any of the .o's.  
+       let dlls = [ dll | DLL dll <- classifieds ]
+           objs = [ obj | Object obj <- classifieds ]
 
        maybePutStr dflags ("Loading package " ++ name pkg ++ " ... ")
-        mapM loadClassified sos_first
+
+       -- 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) $ 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
+
         maybePutStr dflags "linking ... "
         ok <- resolveObjs
        if ok then maybePutStrLn dflags "done."
              else panic ("can't load package `" ++ name pkg ++ "'")
-     where
-        isRight (Right _) = True
-        isRight (Left _)  = False
-
-loadClassified :: LibrarySpec -> IO ()
-loadClassified (Left obj_absolute_filename)
-   = do loadObj obj_absolute_filename
-loadClassified (Right dll_unadorned)
-   = do maybe_errmsg <- addDLL "" dll_unadorned -- doesn't seem right to me
-        if    maybe_errmsg == nullPtr
-         then return ()
-         else do str <- peekCString maybe_errmsg
-                 throwDyn (CmdLineError ("can't load .so/.DLL for: " 
-                                       ++ dll_unadorned ++ " (" ++ str ++ ")" ))
 
+loadDynamics dirs [] = return ()
+loadDynamics dirs (dll:dlls) = do
+  r <- loadDynamic dirs dll
+  case r of
+    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.
 locateOneObj :: [FilePath] -> String -> IO LibrarySpec
-locateOneObj []     obj 
-   = return (Right obj) -- we assume
-locateOneObj (d:ds) obj 
-   = do let path = d ++ '/':obj ++ ".o"
+locateOneObj [] lib
+   = return (DLL lib) -- we assume
+locateOneObj (d:ds) lib
+   = do let path = d ++ '/':lib ++ ".o"
         b <- doesFileExist path
-        if b then return (Left path) else locateOneObj ds obj
+        if b then return (Object path) else locateOneObj ds lib
+
+-- ----------------------------------------------------------------------------
+-- Loading a dyanmic library (dlopen()-ish on Unix, LoadLibrary-ish on Win32)
+
+#if defined(mingw32_TARGET_OS) || defined(cygwin32_TARGET_OS)
+loadDynamic paths rootname = addDLL rootname
+  -- ignore paths on windows (why? --SDM)
+
+#else
+
+-- return Nothing == success, else Just error message from dlopen
+loadDynamic (path:paths) rootname = do
+  let dll = path ++ '/':mkSOName rootname
+  b <- doesFileExist dll
+  if not b
+     then loadDynamic paths rootname
+     else addDLL dll
+loadDynamic [] rootname = do
+       -- tried all our known library paths, let dlopen() search its
+       -- 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)
+addDLL str = do
+  maybe_errmsg <- withCString str $ \dll -> c_addDLL dll
+  if maybe_errmsg == nullPtr
+       then return Nothing
+       else do str <- peekCString maybe_errmsg
+               return (Just str)
+
+foreign import ccall "addDLL" unsafe  
+  c_addDLL :: CString -> IO CString
 
 -----------------------------------------------------------------------------
 -- timing & statistics
@@ -1164,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