[project @ 2000-11-15 10:49:53 by sewardj]
[ghc-hetmet.git] / ghc / compiler / compMan / CmLink.lhs
1 %
2 % (c) The University of Glasgow, 2000
3 %
4 \section[CmLink]{Linker for GHCI}
5
6 \begin{code}
7 module CmLink ( Linkable(..),  Unlinked(..),
8                 filterModuleLinkables, 
9                 modname_of_linkable, is_package_linkable,
10                 LinkResult(..),
11                 link, 
12                 PersistentLinkerState{-abstractly!-}, emptyPLS )
13 where
14
15
16 import Interpreter
17 import CmStaticInfo     ( PackageConfigInfo, GhciMode(..) )
18 import Module           ( ModuleName, PackageName )
19 import Outputable       ( SDoc )
20 import Digraph          ( SCC(..), flattenSCC, flattenSCCs )
21 import Outputable
22 import Panic            ( panic )
23
24 #include "HsVersions.h"
25 \end{code}
26
27 \begin{code}
28 data PersistentLinkerState 
29    = PersistentLinkerState {
30
31 #ifdef GHCI
32         -- Current global mapping from RdrNames to closure addresses
33         closure_env :: ClosureEnv,
34
35         -- the current global mapping from RdrNames of DataCons to 
36         -- info table addresses.
37         -- When a new Unlinked is linked into the running image, or an existing
38         -- module in the image is replaced, the itbl_env must be updated
39         -- appropriately.
40         itbl_env    :: ItblEnv
41
42         -- notionally here, but really lives in the C part of the linker:
43         --            object_symtab :: FiniteMap String Addr
44 #else
45         dummy :: ()     --  sigh, can't have an empty record
46 #endif
47
48      }
49
50 data LinkResult 
51    = LinkOK   PersistentLinkerState
52    | LinkErrs PersistentLinkerState [SDoc]
53
54 data Unlinked
55    = DotO FilePath
56    | DotA FilePath
57    | DotDLL FilePath
58    | Trees [UnlinkedIBind] ItblEnv  -- bunch of interpretable bindings, +
59                                     -- a mapping from DataCons to their itbls
60
61 instance Outputable Unlinked where
62    ppr (DotO path)   = text "DotO" <+> text path
63    ppr (DotA path)   = text "DotA" <+> text path
64    ppr (DotDLL path) = text "DotDLL" <+> text path
65    ppr (Trees binds _) = text "Trees" <+> ppr binds
66
67
68 isObject (DotO _) = True
69 isObject (DotA _) = True
70 isObject (DotDLL _) = True
71 isObject _ = False
72
73 nameOfObject (DotO fn)   = fn
74 nameOfObject (DotA fn)   = fn
75 nameOfObject (DotDLL fn) = fn
76
77 isInterpretable (Trees _ _) = True
78 isInterpretable _ = False
79
80 data Linkable
81    = LM ModuleName [Unlinked]
82    | LP PackageName
83
84 instance Outputable Linkable where
85    ppr (LM mod_nm unlinkeds) = text "LinkableM" <+> ppr mod_nm <+> ppr unlinkeds
86    ppr (LP package_nm)       = text "LinkableP" <+> ptext package_nm
87
88 emptyPLS :: IO PersistentLinkerState
89 #ifdef GHCI
90 emptyPLS = return (PersistentLinkerState { closure_env = emptyFM, 
91                                            itbl_env    = emptyFM })
92 #else
93 emptyPLS = return (PersistentLinkerState {})
94 #endif
95 \end{code}
96
97 \begin{code}
98 -- The first arg is supposed to be DriverPipeline.doLink.
99 -- Passed in here to avoid a hard-to-avoid circular dependency
100 -- between CmLink and DriverPipeline.  Same deal as with
101 -- CmSummarise.summarise.
102 link :: ([String] -> IO ()) 
103      -> GhciMode                -- interactive or batch
104      -> Bool                    -- attempt linking in batch mode?
105      -> PackageConfigInfo 
106      -> [SCC Linkable] 
107      -> PersistentLinkerState 
108      -> IO LinkResult
109
110 #ifndef GHCI_NOTYET
111 --link = panic "CmLink.link: not implemented"
112
113 -- For the moment, in the batch linker, we don't bother to
114 -- tell doLink which packages to link -- it just tries all that
115 -- are available.
116 -- batch_attempt_linking should only be *looked at* in 
117 -- batch mode.  It should only be True if the upsweep was
118 -- successful and someone exports main, i.e., we have good
119 -- reason to believe that linking will succeed.
120 link doLink Batch batch_attempt_linking pci groups pls1
121    | batch_attempt_linking
122    = do putStrLn "LINK(batch): linkables are ..."
123         putStrLn (showSDoc (vcat (map ppLinkableSCC groups)))
124         let o_files = concatMap getOfiles (flattenSCCs groups)
125         doLink o_files
126         -- doLink only returns if it succeeds
127         putStrLn "LINK(batch): done"
128         return (LinkOK pls1)
129    | otherwise
130    = do putStrLn "LINKER(batch): upsweep (partially?) failed OR main not exported;"
131         putStrLn "               -- not doing linking"
132         return (LinkOK pls1)
133    where
134       getOfiles (LP _)    = []
135       getOfiles (LM _ us) = map nameOfObject (filter isObject us)
136
137 link doLink Interactive batch_attempt_linking pci groups pls1
138    = do putStrLn "LINKER(interactive): not yet implemented"
139         return (LinkOK pls1)
140
141
142 ppLinkableSCC :: SCC Linkable -> SDoc
143 ppLinkableSCC = ppr . flattenSCC
144
145 #else
146
147
148 link pci [] pls = return (LinkOK pls)
149 link pci (groupSCC:groups) pls = do
150    let group = flattenSCC groupSCC
151    -- the group is either all objects or all interpretable, for now
152    if all isObject group
153         then do mapM loadObj [ file | DotO file <- group ]
154                 resolveObjs
155                 link pci groups pls
156     else if all isInterpretable group
157         then do (new_closure_env, new_itbl_env) <-
158                    linkIModules (closure_env pls)
159                                 (itbl_env pls)
160                                 [ trees | Trees trees <- group ]
161                 link pci groups (PersistentLinkerState{
162                                    closure_env=new_closure_env,
163                                    itbl_env=new_itbl_env})
164     else
165         return (LinkErrs pls (ptext SLIT("linker: group must contain all objects or all interpreted modules")))
166 #endif
167
168
169 modname_of_linkable (LM nm _) = nm
170 modname_of_linkable (LP _)    = panic "modname_of_linkable: package"
171
172 is_package_linkable (LP _)   = True
173 is_package_linkable (LM _ _) = False
174
175 filterModuleLinkables :: (ModuleName -> Bool) 
176                       -> [Linkable] 
177                       -> [Linkable]
178 filterModuleLinkables p [] = []
179 filterModuleLinkables p (li:lis)
180    = case li of
181         LP _       -> retain
182         LM modnm _ -> if p modnm then retain else dump
183      where
184         dump   = filterModuleLinkables p lis
185         retain = li : dump
186 \end{code}