Re-working of the breakpoint support
[ghc-hetmet.git] / compiler / ghci / Linker.lhs
index 640fc9d..38d584a 100644 (file)
@@ -18,7 +18,7 @@ module Linker ( HValue, getHValue, showLinkerState,
                linkExpr, unload, extendLinkEnv, withExtendedLinkEnv,
                 extendLoadedPkgs,
                linkPackages,initDynLinker,
-                recoverDataCon
+                dataConInfoPtrToName
        ) where
 
 #include "HsVersions.h"
@@ -28,13 +28,10 @@ import ByteCodeLink
 import ByteCodeItbls
 import ByteCodeAsm
 import RtClosureInspect
-import Var
+import CgInfoTbls
+import SMRep
 import IfaceEnv
-import Config
-import OccName
 import TcRnMonad
-import Constants
-import Encoding
 import Packages
 import DriverPhases
 import Finder
@@ -42,6 +39,7 @@ import HscTypes
 import Name
 import NameEnv
 import NameSet
+import qualified OccName
 import UniqFM
 import Module
 import ListSetOps
@@ -55,27 +53,24 @@ import StaticFlags
 import ErrUtils
 import DriverPhases
 import SrcLoc
+import UniqSet
+import Constants
 
 -- Standard libraries
 import Control.Monad
-import Control.Arrow    ( second )
 
 import Data.IORef
 import Data.List
 import Foreign.Ptr
-import GHC.Exts
+import Foreign.C.Types
+import Foreign.C.String
+import Foreign.Storable
 
 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}
 
 
@@ -119,7 +114,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
@@ -128,9 +122,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.
   --
@@ -152,57 +145,107 @@ extendLinkEnv new_bindings
            new_pls = pls { closure_env = new_closure_env }
        writeIORef v_PersistentLinkerState new_pls
 
+-- | Given a data constructor, find its internal name.
+--   The info tables for data constructors have a field which records the source name
+--   of the constructor as a CString. 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 Name
+dataConInfoPtrToName x = do 
+   theString <- ioToTcRn $ do
+      let ptr = castPtr x :: Ptr StgInfoTable
+      conDescAddress <- getConDescAddress ptr 
+      str <- peekCString conDescAddress  
+      return str
+   let (pkg, mod, occ) = parse theString 
+       occName = mkOccName OccName.dataName occ
+       modName = mkModule (stringToPackageId pkg) (mkModuleName mod) 
+   lookupOrig modName occName
 
-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)
-
--- | 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 
-   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
+   where
+
+   {- 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 CChar)
+   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) + stdInfoTableSizeB
+#endif
+
+   -- 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 :: String -> (String, String, String)
+   parse input 
+      = ASSERT (all (>0) (map length [pkg, mod, occ])) (pkg, mod, occ)
+      where
+      (pkg, rest1) = break (==':') input 
+      (mod, occ) 
+         = (concat $ intersperse "." $ reverse modWords, occWord)
+         where
+         (modWords, occWord) = ASSERT (length rest1 > 0) (parseModOcc [] (tail rest1))
+      parseModOcc :: [String] -> String -> ([String], String)
+      parseModOcc acc str
+         = case break (== '.') str of
+              (top, []) -> (acc, top)
+              (top, '.':bot) -> parseModOcc (top : acc) bot
+       
 
 getHValue :: Name -> IO (Maybe HValue)
 getHValue name = do
     pls <- readIORef v_PersistentLinkerState
-    return$ fmap snd (lookupNameEnv (closure_env pls) name)
+    case lookupNameEnv (closure_env pls) name of
+      Just (_,x) -> return$ Just x
+      _          -> return Nothing
 
 withExtendedLinkEnv :: [(Name,HValue)] -> IO a -> IO a
 withExtendedLinkEnv new_env action
@@ -239,9 +282,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}
                        
        
@@ -423,11 +464,9 @@ 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
@@ -474,17 +513,18 @@ getLinkDeps hsc_env hpt pit maybe_normal_osuf span mods
  = do {        pls <- readIORef v_PersistentLinkerState ;
        let {
        -- 1.  Find the dependent home-pkg-modules/packages from each iface
-           (mods_s, pkgs_s) = unzip (map get_deps mods) ;
+           (mods_s, pkgs_s) = follow_deps mods emptyUniqSet emptyUniqSet;
 
        -- 2.  Exclude ones already linked
        --      Main reason: avoid findModule calls in get_linkable
-           mods_needed = nub (concat mods_s) `minusList` linked_mods     ;
-           pkgs_needed = nub (concat pkgs_s) `minusList` pkgs_loaded pls ;
+           mods_needed = mods_s `minusList` linked_mods     ;
+           pkgs_needed = pkgs_s `minusList` pkgs_loaded pls ;
 
            linked_mods = map (moduleName.linkableModule) 
                                 (objs_loaded pls ++ bcos_loaded pls)
        } ;
        
+--        putStrLn (showSDoc (ppr mods_s)) ;
        -- 3.  For each dependent module, find its linkable
        --     This will either be in the HPT or (in the case of one-shot
        --     compilation) we may need to use maybe_getFileLinkable
@@ -495,17 +535,43 @@ getLinkDeps hsc_env hpt pit maybe_normal_osuf span mods
     dflags = hsc_dflags hsc_env
     this_pkg = thisPackage dflags
 
-    get_deps :: Module -> ([ModuleName],[PackageId])
-       -- Get the things needed for the specified module
-       -- This is rather similar to the code in RnNames.importsFromImportDecl
-    get_deps mod
+        -- The ModIface contains the transitive closure of the module dependencies
+        -- within the current package, *except* for boot modules: if we encounter
+        -- a boot module, we have to find its real interface and discover the
+        -- dependencies of that.  Hence we need to traverse the dependency
+        -- tree recursively.  See bug #936, testcase ghci/prog007.
+    follow_deps :: [Module]             -- modules to follow
+                -> UniqSet ModuleName         -- accum. module dependencies
+                -> UniqSet PackageId          -- accum. package dependencies
+                -> ([ModuleName], [PackageId]) -- result
+    follow_deps []     acc_mods acc_pkgs
+        = (uniqSetToList acc_mods, uniqSetToList acc_pkgs)
+    follow_deps (mod:mods) acc_mods acc_pkgs
         | pkg /= this_pkg
-        = ([], pkg : dep_pkgs deps)
+        = follow_deps mods acc_mods (addOneToUniqSet acc_pkgs' pkg)
+        | mi_boot iface
+        = link_boot_mod_error mod
        | otherwise
-       = (moduleName mod : [m | (m,_) <- dep_mods deps], dep_pkgs deps)
-       where
-          pkg   = modulePackageId mod
-         deps  = mi_deps (get_iface mod)
+        = follow_deps (map (mkModule this_pkg) boot_deps ++ mods) acc_mods' acc_pkgs'
+      where
+        pkg   = modulePackageId mod
+        iface = get_iface mod
+       deps  = mi_deps iface
+
+       pkg_deps = dep_pkgs deps
+        (boot_deps, mod_deps) = partitionWith is_boot (dep_mods deps)
+                where is_boot (m,True)  = Left m
+                      is_boot (m,False) = Right m
+
+        boot_deps' = filter (not . (`elementOfUniqSet` acc_mods)) boot_deps
+        acc_mods'  = addListToUniqSet acc_mods (moduleName mod : mod_deps)
+        acc_pkgs'  = addListToUniqSet acc_pkgs pkg_deps
+
+
+    link_boot_mod_error mod = 
+        throwDyn (ProgramError (showSDoc (
+            text "module" <+> ppr mod <+> 
+            text "cannot be linked; it is only available as a boot module")))
 
     get_iface mod = case lookupIfaceByModule dflags hpt pit mod of
                            Just iface -> iface
@@ -687,11 +753,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
@@ -702,14 +767,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)
@@ -722,22 +786,8 @@ 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
-            refs  = goForRefs ul_bcos
-            names = nub$ concatMap (ssElts . unlinkedBCOItbls) (ul_bcos ++ refs)
-        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)
-    where 
-          goForRefs = getRefs []
-          getRefs acc []  = acc
-          getRefs acc new = getRefs (new++acc) 
-                 [bco | BCOPtrBCO bco <- concatMap (ssElts . unlinkedBCOPtrs) new
-                      , notElemBy bco (new ++ acc) nameEq]
-          ul1 `nameEq` ul2 = unlinkedBCOName ul1 == unlinkedBCOName ul2
-          (x1 `notElemBy` x2) eq = null$ intersectBy eq [x1] x2
+        return (ce_out, hvals)
+
 \end{code}