Add {-# OPTIONS_GHC -w #-} and some blurb to all compiler modules
[ghc-hetmet.git] / compiler / ghci / Linker.lhs
index d2c7fe1..6f000c5 100644 (file)
@@ -14,11 +14,19 @@ necessary.
 \begin{code}
 {-# OPTIONS -optc-DNON_POSIX_SOURCE -#include "Linker.h" #-}
 
+{-# OPTIONS_GHC -w #-}
+-- The above warning supression flag is a temporary kludge.
+-- While working on this module you are encouraged to remove it and fix
+-- any warnings in the module. See
+--     http://hackage.haskell.org/trac/ghc/wiki/WorkingConventions#Warnings
+-- for details
+
 module Linker ( HValue, getHValue, showLinkerState,
-               linkExpr, unload, extendLinkEnv, withExtendedLinkEnv,
-                extendLoadedPkgs,
+               linkExpr, unload, withExtendedLinkEnv,
+                extendLinkEnv, deleteFromLinkEnv,
+                extendLoadedPkgs, 
                linkPackages,initDynLinker,
-                recoverDataCon
+                dataConInfoPtrToName
        ) where
 
 #include "HsVersions.h"
@@ -27,13 +35,10 @@ import ObjLink
 import ByteCodeLink
 import ByteCodeItbls
 import ByteCodeAsm
-import RtClosureInspect
+import CgInfoTbls
+import SMRep
 import IfaceEnv
-import Config
-import OccName
 import TcRnMonad
-import Constants
-import Encoding
 import Packages
 import DriverPhases
 import Finder
@@ -41,6 +46,7 @@ import HscTypes
 import Name
 import NameEnv
 import NameSet
+import qualified OccName
 import UniqFM
 import Module
 import ListSetOps
@@ -55,26 +61,23 @@ import ErrUtils
 import DriverPhases
 import SrcLoc
 import UniqSet
+import Constants
+import FastString
+import Config          ( cProjectVersion )
 
 -- Standard libraries
 import Control.Monad
-import Control.Arrow    ( second )
 
+import Data.Char
 import Data.IORef
 import Data.List
-import Foreign.Ptr
+import Foreign
 
 import System.IO
 import System.Directory
 
 import Control.Exception
 import Data.Maybe
-
-#if __GLASGOW_HASKELL__ >= 503
-import GHC.IOBase      ( IO(..) )
-#else
-import PrelIOBase      ( IO(..) )
-#endif
 \end{code}
 
 
@@ -118,7 +121,6 @@ data PersistentLinkerState
        -- Held, as usual, in dependency order; though I am not sure if
        -- that is really important
        pkgs_loaded :: [PackageId]
-       ,dtacons_env :: DataConEnv
      }
 
 emptyPLS :: DynFlags -> PersistentLinkerState
@@ -127,9 +129,8 @@ emptyPLS dflags = PersistentLinkerState {
                        itbl_env    = emptyNameEnv,
                        pkgs_loaded = init_pkgs,
                        bcos_loaded = [],
-                       objs_loaded = []
-                      , dtacons_env = emptyAddressEnv
-                                        }
+                       objs_loaded = [] }
+                    
   -- Packages that don't need loading, because the compiler 
   -- shares them with the interpreted program.
   --
@@ -151,71 +152,166 @@ extendLinkEnv new_bindings
            new_pls = pls { closure_env = new_closure_env }
        writeIORef v_PersistentLinkerState new_pls
 
+deleteFromLinkEnv :: [Name] -> IO ()
+deleteFromLinkEnv to_remove
+  = do pls <- readIORef v_PersistentLinkerState
+       let new_closure_env = delListFromNameEnv (closure_env pls) to_remove
+           new_pls = pls { closure_env = new_closure_env }
+       writeIORef v_PersistentLinkerState new_pls
+
+-- | Given a data constructor in the heap, find its Name.
+--   The info tables for data constructors have a field which records
+--   the source name of the constructor as a Ptr Word8 (UTF-8 encoded
+--   string). The format is:
+--
+--    Package:Module.Name
+--
+--   We use this string to lookup the interpreter's internal representation of the name
+--   using the lookupOrig.    
+
+dataConInfoPtrToName :: Ptr () -> TcM (Either String Name)
+dataConInfoPtrToName x = do 
+   theString <- ioToTcRn $ do
+      let ptr = castPtr x :: Ptr StgInfoTable
+      conDescAddress <- getConDescAddress ptr 
+      peekArray0 0 conDescAddress  
+   let (pkg, mod, occ) = parse theString 
+       pkgFS = mkFastStringByteList pkg
+       modFS = mkFastStringByteList mod
+       occFS = mkFastStringByteList occ
+       occName = mkOccNameFS OccName.dataName occFS
+       modName = mkModule (fsToPackageId pkgFS) (mkModuleNameFS modFS) 
+   return (Left$ showSDoc$ ppr modName <> dot <> ppr occName ) 
+    `recoverM` (Right `fmap` lookupOrig modName occName)
+
+   where
 
-recoverDataCon :: a -> TcM Name
-recoverDataCon a = recoverDCInRTS a `recoverM` ioToTcRn (do 
-               mb_name <- recoverDCInDynEnv a
-               maybe (fail "Linker.recoverDatacon: Name not found in Dyn Env")
-                     return
-                     mb_name)
+   {- To find the string in the constructor's info table we need to consider 
+      the layout of info tables relative to the entry code for a closure.
+
+      An info table can be next to the entry code for the closure, or it can
+      be separate. The former (faster) is used in registerised versions of ghc, 
+      and the latter (portable) is for non-registerised versions. 
+
+      The diagrams below show where the string is to be found relative to 
+      the normal info table of the closure.
+
+      1) Code next to table:
+
+         --------------
+         |            |   <- pointer to the start of the string
+         --------------
+         |            |   <- the (start of the) info table structure
+         |            |
+         |            |
+         --------------
+         | entry code | 
+         |    ....    |
+
+         In this case the pointer to the start of the string can be found in
+         the memory location _one word before_ the first entry in the normal info 
+         table.
+
+      2) Code NOT next to table:
+
+                                 --------------
+         info table structure -> |     *------------------> --------------
+                                 |            |             | entry code |
+                                 |            |             |    ....    | 
+                                 --------------
+         ptr to start of str ->  |            |   
+                                 --------------
+
+         In this case the pointer to the start of the string can be found
+         in the memory location: info_table_ptr + info_table_size
+   -}
+
+   getConDescAddress :: Ptr StgInfoTable -> IO (Ptr Word8)
+   getConDescAddress ptr = do
+#ifdef GHCI_TABLES_NEXT_TO_CODE
+       offsetToString <- peek $ ptr `plusPtr` (- wORD_SIZE)
+       return $ (ptr `plusPtr` stdInfoTableSizeB) `plusPtr` (fromIntegral (offsetToString :: StgWord))
+#else
+       peek $ intPtrToPtr $ (ptrToIntPtr ptr) + fromIntegral stdInfoTableSizeB
+#endif
 
--- | If a is a Constr closure, lookupDC returns either the Name of the DataCon or the
---   symbol if it is a nullary constructor
---   For instance, for a closure containing 'Just x' it would return the Name for Data.Maybe.Just
---   For a closure containing 'Nothing' it would return the String "DataziMaybe_Nothing_static_info"
-recoverDCInDynEnv :: a -> IO (Maybe Name)
-recoverDCInDynEnv a = do 
+   -- parsing names is a little bit fiddly because we have a string in the form: 
+   -- pkg:A.B.C.foo, and we want to split it into three parts: ("pkg", "A.B.C", "foo").
+   -- Thus we split at the leftmost colon and the rightmost occurrence of the dot.
+   -- It would be easier if the string was in the form pkg:A.B.C:foo, but alas
+   -- this is not the conventional way of writing Haskell names. We stick with
+   -- convention, even though it makes the parsing code more troublesome.
+   -- Warning: this code assumes that the string is well formed.
+   parse :: [Word8] -> ([Word8], [Word8], [Word8])
+   parse input 
+      = ASSERT (all (>0) (map length [pkg, mod, occ])) (pkg, mod, occ)
+      where
+      dot = fromIntegral (ord '.')
+      (pkg, rest1) = break (== fromIntegral (ord ':')) input 
+      (mod, occ) 
+         = (concat $ intersperse [dot] $ reverse modWords, occWord)
+         where
+         (modWords, occWord) = ASSERT (length rest1 > 0) (parseModOcc [] (tail rest1))
+      parseModOcc :: [[Word8]] -> [Word8] -> ([[Word8]], [Word8])
+      parseModOcc acc str
+         = case break (== dot) str of
+              (top, []) -> (acc, top)
+              (top, _:bot) -> parseModOcc (top : acc) bot
+       
+
+getHValue :: HscEnv -> Name -> IO HValue
+getHValue hsc_env name = do
+   when (isExternalName name) $ do
+        ok <- linkDependencies hsc_env noSrcSpan [nameModule name]
+        when (failed ok) $ throwDyn (ProgramError "")
    pls <- readIORef v_PersistentLinkerState
-   let de = dtacons_env pls
-   ctype <- getClosureType a
-   if not (isConstr ctype) 
-         then putStrLn ("Not a Constr (" ++ show  ctype ++ ")") >> 
-              return Nothing
-         else do let infot = getInfoTablePtr a
-                     name  = lookupAddressEnv de (castPtr$ infot `plusPtr` (wORD_SIZE*2))
-                 return name
-
-
-recoverDCInRTS :: a -> TcM Name 
-recoverDCInRTS a = do
-  ctype <- ioToTcRn$ getClosureType a
-  if (not$ isConstr ctype)
-     then fail "not Constr"
-     else do
-       Just symbol <- ioToTcRn$ lookupDataCon (getInfoTablePtr a)
-       let (occ,mod) = (parse . lex) symbol
-       lookupOrig mod occ
-    where lex x = map zDecodeString . init . init . split '_' . removeLeadingUnderscore $ x
-          parse [pkg, modName, occ] = (mkOccName OccName.dataName occ,
-              mkModule (stringToPackageId pkg) (mkModuleName modName))
-          parse [modName, occ] = (mkOccName OccName.dataName occ,
-              mkModule mainPackageId (mkModuleName modName))
-          split delim = let 
-                 helper [] = Nothing
-                 helper x  = Just . second (drop 1) . break (==delim) $ x
-              in unfoldr helper
-          removeLeadingUnderscore = if cLeadingUnderscore=="YES" 
-                                       then tail 
-                                       else id
-
-getHValue :: Name -> IO (Maybe HValue)
-getHValue name = do
-    pls <- readIORef v_PersistentLinkerState
-    case lookupNameEnv (closure_env pls) name of
-      Just (_,x) -> return$ Just x
-      _          -> return Nothing
+   lookupName (closure_env pls) name
+        
+linkDependencies :: HscEnv -> SrcSpan -> [Module] -> IO SuccessFlag
+linkDependencies hsc_env span needed_mods = do
+   let hpt = hsc_HPT hsc_env
+       dflags = hsc_dflags hsc_env
+       -- The interpreter and dynamic linker can only handle object code built
+       -- the "normal" way, i.e. no non-std ways like profiling or ticky-ticky.
+       -- So here we check the build tag: if we're building a non-standard way
+       -- then we need to find & link object files built the "normal" way.
+   maybe_normal_osuf <- checkNonStdWay dflags span
+
+       -- Find what packages and linkables are required
+   eps <- readIORef (hsc_EPS hsc_env)
+   (lnks, pkgs) <- getLinkDeps hsc_env hpt (eps_PIT eps) 
+                               maybe_normal_osuf span needed_mods
+
+       -- Link the packages and modules required
+   linkPackages dflags pkgs
+   linkModules dflags lnks
+
+
+-- | Temporarily extend the linker state.
 
 withExtendedLinkEnv :: [(Name,HValue)] -> IO a -> IO a
 withExtendedLinkEnv new_env action
     = bracket set_new_env
               reset_old_env
               (const action)
-    where set_new_env = do pls <- readIORef v_PersistentLinkerState
-                           let new_closure_env = extendClosureEnv (closure_env pls) new_env
-                               new_pls = pls { closure_env = new_closure_env }
-                           writeIORef v_PersistentLinkerState new_pls
-                           return (closure_env pls)
-          reset_old_env env = modifyIORef v_PersistentLinkerState (\pls -> pls{ closure_env = env })
+    where set_new_env = do 
+            pls <- readIORef v_PersistentLinkerState
+            let new_closure_env = extendClosureEnv (closure_env pls) new_env
+                new_pls = pls { closure_env = new_closure_env }
+            writeIORef v_PersistentLinkerState new_pls
+            return (closure_env pls)
+
+        -- Remember that the linker state might be side-effected
+        -- during the execution of the IO action, and we don't want to
+        -- lose those changes (we might have linked a new module or
+        -- package), so the reset action only removes the names we
+        -- added earlier.
+          reset_old_env env = do
+            modifyIORef v_PersistentLinkerState $ \pls ->
+                let cur = closure_env pls
+                    new = delListFromNameEnv cur (map fst new_env)
+                in
+                pls{ closure_env = new }
 
 -- filterNameMap removes from the environment all entries except 
 --     those for a given set of modules;
@@ -240,9 +336,7 @@ showLinkerState
        printDump (vcat [text "----- Linker state -----",
                        text "Pkgs:" <+> ppr (pkgs_loaded pls),
                        text "Objs:" <+> ppr (objs_loaded pls),
-                       text "BCOs:" <+> ppr (bcos_loaded pls),
-                        text "DataCons:" <+> ppr (dtacons_env pls)
-                       ])
+                       text "BCOs:" <+> ppr (bcos_loaded pls)])
 \end{code}
                        
        
@@ -402,20 +496,8 @@ linkExpr hsc_env span root_ul_bco
      let dflags = hsc_dflags hsc_env
    ; initDynLinker dflags
 
-       -- The interpreter and dynamic linker can only handle object code built
-       -- the "normal" way, i.e. no non-std ways like profiling or ticky-ticky.
-       -- So here we check the build tag: if we're building a non-standard way
-       -- then we need to find & link object files built the "normal" way.
-   ; maybe_normal_osuf <- checkNonStdWay dflags span
-
-       -- Find what packages and linkables are required
-   ; eps <- readIORef (hsc_EPS hsc_env)
-   ; (lnks, pkgs) <- getLinkDeps hsc_env hpt (eps_PIT eps) 
-                               maybe_normal_osuf span needed_mods
-
        -- Link the packages and modules required
-   ; linkPackages dflags pkgs
-   ; ok <- linkModules dflags lnks
+   ; ok <- linkDependencies hsc_env span needed_mods
    ; if failed ok then
        throwDyn (ProgramError "")
      else do {
@@ -424,15 +506,12 @@ linkExpr hsc_env span root_ul_bco
      pls <- readIORef v_PersistentLinkerState
    ; let ie = itbl_env pls
         ce = closure_env pls
-         de = dtacons_env pls
 
        -- Link the necessary packages and linkables
-   ; (_,de_out, (root_hval:_)) <- linkSomeBCOs False ie ce de [root_ul_bco]
-   ; writeIORef v_PersistentLinkerState (pls{dtacons_env=de_out})
+   ; (_, (root_hval:_)) <- linkSomeBCOs False ie ce [root_ul_bco]
    ; return root_hval
    }}
    where
-     hpt    = hsc_HPT hsc_env
      free_names = nameSetToList (bcoFreeNames root_ul_bco)
 
      needed_mods :: [Module]
@@ -514,7 +593,7 @@ getLinkDeps hsc_env hpt pit maybe_normal_osuf span mods
         | mi_boot iface
         = link_boot_mod_error mod
        | otherwise
-        = follow_deps (map (mkModule this_pkg) boot_deps ++ mods) acc_mods' acc_pkgs'
+        = follow_deps (map (mkModule this_pkg) boot_deps' ++ mods) acc_mods' acc_pkgs'
       where
         pkg   = modulePackageId mod
         iface = get_iface mod
@@ -715,11 +794,10 @@ dynLinkBCOs bcos
            gce       = closure_env pls
             final_ie  = foldr plusNameEnv (itbl_env pls) ies
 
-        (final_gce, final_de, linked_bcos) <- linkSomeBCOs True final_ie gce (dtacons_env pls) ul_bcos
+        (final_gce, linked_bcos) <- linkSomeBCOs True final_ie gce ul_bcos
                -- What happens to these linked_bcos?
 
        let pls2 = pls1 { closure_env = final_gce,
-                          dtacons_env = final_de, 
                          itbl_env    = final_ie }
 
        writeIORef v_PersistentLinkerState pls2
@@ -730,14 +808,13 @@ linkSomeBCOs :: Bool      -- False <=> add _all_ BCOs to returned closure env
                         -- True  <=> add only toplevel BCOs to closure env
              -> ItblEnv 
              -> ClosureEnv 
-             -> DataConEnv
              -> [UnlinkedBCO]
-             -> IO (ClosureEnv, DataConEnv, [HValue])
+             -> IO (ClosureEnv, [HValue])
                        -- The returned HValues are associated 1-1 with
                        -- the incoming unlinked BCOs.  Each gives the
                        -- value of the corresponding unlinked BCO
                                        
-linkSomeBCOs toplevs_only ie ce_in de_in ul_bcos
+linkSomeBCOs toplevs_only ie ce_in ul_bcos
    = do let nms = map unlinkedBCOName ul_bcos
         hvals <- fixIO 
                     ( \ hvs -> let ce_out = extendClosureEnv ce_in (zipLazy nms hvs)
@@ -750,13 +827,7 @@ linkSomeBCOs toplevs_only ie ce_in de_in ul_bcos
                     -- closure environment, which leads to trouble.
                     ASSERT (all (not . (`elemNameEnv` ce_in)) (map fst ce_additions))
                     extendClosureEnv ce_in ce_additions
-            names = concatMap (ssElts . unlinkedBCOItbls) ul_bcos
-        addresses <- mapM (lookupIE ie) names
-        let de_additions = [(address, name) | (address, name) <- zip addresses names
-                                            , not(address `elemAddressEnv` de_in) 
-                           ]
-            de_out = extendAddressEnvList de_in de_additions
-        return ( ce_out, de_out, hvals)
+        return (ce_out, hvals)
 
 \end{code}
 
@@ -995,6 +1066,9 @@ loadFrameworks pkg = mapM_ load frameworks
 
 -- 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.
+#ifndef __PIC__
+-- When the GHC package was not compiled as dynamic library (=__PIC__ not set),
+-- we search for .o libraries first.
 locateOneObj :: [FilePath] -> String -> IO LibrarySpec
 locateOneObj dirs lib
   = do { mb_obj_path <- findFile mk_obj_path dirs 
@@ -1003,12 +1077,28 @@ locateOneObj dirs lib
            Nothing       -> 
                 do { mb_lib_path <- findFile mk_dyn_lib_path dirs
                    ; case mb_lib_path of
-                       Just lib_path -> return (DLL (lib ++ "_dyn"))
+                       Just lib_path -> return (DLL (lib ++ "-ghc" ++ cProjectVersion))
                        Nothing       -> return (DLL lib) }}            -- We assume
    where
      mk_obj_path dir = dir `joinFileName` (lib `joinFileExt` "o")
-     mk_dyn_lib_path dir = dir `joinFileName` mkSOName (lib ++ "_dyn")
-
+     mk_dyn_lib_path dir = dir `joinFileName` mkSOName (lib ++ "-ghc" ++ cProjectVersion)
+#else
+-- When the GHC package was compiled as dynamic library (=__PIC__ set),
+-- we search for .so libraries first.
+locateOneObj :: [FilePath] -> String -> IO LibrarySpec
+locateOneObj dirs lib
+  = do { mb_lib_path <- findFile mk_dyn_lib_path dirs
+       ; case mb_lib_path of
+           Just lib_path -> return (DLL (lib ++ "-ghc" ++ cProjectVersion))
+           Nothing       ->
+                do { mb_obj_path <- findFile mk_obj_path dirs
+                   ; case mb_obj_path of
+                       Just obj_path -> return (Object obj_path)
+                       Nothing       -> return (DLL lib) }}            -- We assume
+   where
+     mk_obj_path dir = dir `joinFileName` (lib `joinFileExt` "o")
+     mk_dyn_lib_path dir = dir `joinFileName` mkSOName (lib ++ "-ghc" ++ cProjectVersion)
+#endif
 
 -- ----------------------------------------------------------------------------
 -- Loading a dyanmic library (dlopen()-ish on Unix, LoadLibrary-ish on Win32)