SCM Repository
Annotation of /sml/trunk/src/cm/bootstrap/btcompile.sml
Parent Directory
|
Revision Log
Revision 518 - (view) (download)
1 : | blume | 327 | (* |
2 : | * The bootstrap compiler. | ||
3 : | * (Formerly known as "batch" compiler.) | ||
4 : | * | ||
5 : | * (C) 1999 Lucent Technologies, Bell Laboratories | ||
6 : | * | ||
7 : | * Author: Matthias Blume (blume@kurims.kyoto-u.ac.jp) | ||
8 : | *) | ||
9 : | blume | 452 | functor BootstrapCompileFn (structure MachDepVC : MACHDEP_VC |
10 : | blume | 518 | val os : SMLofNJ.SysInfo.os_kind |
11 : | val load_plugin : string -> bool) :> sig | ||
12 : | blume | 364 | val make' : string option -> bool |
13 : | val make : unit -> bool | ||
14 : | blume | 362 | val deliver' : string option -> bool |
15 : | val deliver : unit -> bool | ||
16 : | val reset : unit -> unit | ||
17 : | blume | 434 | val symval : string -> { get: unit -> int option, set: int option -> unit } |
18 : | blume | 357 | end = struct |
19 : | |||
20 : | blume | 327 | structure EM = GenericVC.ErrorMsg |
21 : | structure E = GenericVC.Environment | ||
22 : | structure SE = GenericVC.CMStaticEnv | ||
23 : | structure BE = GenericVC.BareEnvironment | ||
24 : | structure PS = GenericVC.PersStamps | ||
25 : | structure CoerceEnv = GenericVC.CoerceEnv | ||
26 : | blume | 336 | structure SSV = SpecificSymValFn (structure MachDepVC = MachDepVC |
27 : | val os = os) | ||
28 : | blume | 364 | structure P = OS.Path |
29 : | structure F = OS.FileSys | ||
30 : | blume | 403 | structure BF = MachDepVC.Binfile |
31 : | blume | 327 | |
32 : | blume | 452 | val arch = MachDepVC.architecture |
33 : | val osname = FilenamePolicy.kind2name os | ||
34 : | val archos = concat [arch, "-", osname] | ||
35 : | |||
36 : | blume | 456 | fun init_servers (GroupGraph.GROUP { grouppath, ... }) = |
37 : | blume | 464 | Servers.cmb { archos = archos, |
38 : | root = SrcPath.descr grouppath } | ||
39 : | blume | 456 | |
40 : | blume | 448 | structure Compile = CompileFn (structure MachDepVC = MachDepVC |
41 : | blume | 464 | val compile_there = |
42 : | Servers.compile o SrcPath.descr) | ||
43 : | blume | 360 | |
44 : | blume | 403 | structure BFC = BfcFn (structure MachDepVC = MachDepVC) |
45 : | |||
46 : | blume | 327 | (* instantiate Stabilize... *) |
47 : | blume | 329 | structure Stabilize = |
48 : | blume | 452 | StabilizeFn (fun destroy_state _ i = Compile.evict i |
49 : | blume | 403 | structure MachDepVC = MachDepVC |
50 : | blume | 399 | fun recomp gp g = let |
51 : | blume | 403 | val { store, get } = BFC.new () |
52 : | blume | 456 | val _ = init_servers g |
53 : | blume | 399 | val { group, ... } = |
54 : | blume | 403 | Compile.newTraversal (fn _ => fn _ => (), |
55 : | store, g) | ||
56 : | blume | 399 | in |
57 : | blume | 450 | case Servers.withServers (fn () => group gp) of |
58 : | blume | 403 | NONE => NONE |
59 : | | SOME _ => SOME get | ||
60 : | end | ||
61 : | val getII = Compile.getII) | ||
62 : | blume | 398 | |
63 : | blume | 327 | (* ... and Parse *) |
64 : | blume | 362 | structure Parse = ParseFn (structure Stabilize = Stabilize |
65 : | blume | 372 | fun pending () = SymbolMap.empty) |
66 : | blume | 327 | |
67 : | blume | 366 | (* copying an input file to an output file safely... *) |
68 : | blume | 368 | fun copyFile (oi, ci, oo, co, inp, outp, eof) (inf, outf) = let |
69 : | fun workIn is = let | ||
70 : | fun workOut os = let | ||
71 : | blume | 366 | val N = 4096 |
72 : | fun loop () = | ||
73 : | blume | 368 | if eof is then () else (outp (os, inp (is, N)); loop ()) |
74 : | blume | 366 | in |
75 : | loop () | ||
76 : | end | ||
77 : | in | ||
78 : | blume | 368 | SafeIO.perform { openIt = fn () => oo outf, |
79 : | closeIt = co, | ||
80 : | blume | 366 | work = workOut, |
81 : | blume | 459 | cleanup = fn _ => |
82 : | blume | 366 | (F.remove outf handle _ => ()) } |
83 : | end | ||
84 : | blume | 364 | in |
85 : | blume | 368 | SafeIO.perform { openIt = fn () => oi inf, |
86 : | closeIt = ci, | ||
87 : | blume | 366 | work = workIn, |
88 : | blume | 459 | cleanup = fn _ => () } |
89 : | blume | 364 | end |
90 : | blume | 327 | |
91 : | blume | 368 | val copyTextFile = |
92 : | copyFile (TextIO.openIn, TextIO.closeIn, | ||
93 : | AutoDir.openTextOut, TextIO.closeOut, | ||
94 : | TextIO.inputN, TextIO.output, TextIO.endOfStream) | ||
95 : | |||
96 : | val copyBinFile = | ||
97 : | copyFile (BinIO.openIn, BinIO.closeIn, | ||
98 : | AutoDir.openBinOut, BinIO.closeOut, | ||
99 : | BinIO.inputN, BinIO.output, BinIO.endOfStream) | ||
100 : | |||
101 : | blume | 456 | fun mk_compile deliver root dbopt = let |
102 : | blume | 358 | |
103 : | blume | 360 | val dirbase = getOpt (dbopt, BtNames.dirbaseDefault) |
104 : | val pcmodespec = BtNames.pcmodespec | ||
105 : | val initgspec = BtNames.initgspec | ||
106 : | val maingspec = BtNames.maingspec | ||
107 : | |||
108 : | blume | 452 | val bindir = concat [dirbase, ".bin.", archos] |
109 : | val bootdir = concat [dirbase, ".boot.", archos] | ||
110 : | blume | 357 | |
111 : | blume | 364 | fun listName (p, copy) = |
112 : | case P.fromString p of | ||
113 : | { vol = "", isAbs = false, arcs = arc0 :: arc1 :: arcn } => let | ||
114 : | fun win32name () = | ||
115 : | concat (arc1 :: | ||
116 : | foldr (fn (a, r) => "\\" :: a :: r) [] arcn) | ||
117 : | fun doCopy () = let | ||
118 : | val bootpath = | ||
119 : | P.toString { isAbs = false, vol = "", | ||
120 : | arcs = bootdir :: arc1 :: arcn } | ||
121 : | in | ||
122 : | blume | 368 | copyBinFile (p, bootpath) |
123 : | blume | 364 | end |
124 : | in | ||
125 : | if copy andalso arc0 = bindir then doCopy () else (); | ||
126 : | case os of | ||
127 : | SMLofNJ.SysInfo.WIN32 => win32name () | ||
128 : | | _ => P.toString { isAbs = false, vol = "", | ||
129 : | arcs = arc1 :: arcn } | ||
130 : | end | ||
131 : | | _ => raise Fail "BootstrapCompile:listName: bad name" | ||
132 : | |||
133 : | blume | 433 | val keep_going = #get StdConfig.keep_going () |
134 : | blume | 329 | |
135 : | blume | 354 | val ctxt = SrcPath.cwdContext () |
136 : | blume | 329 | |
137 : | blume | 364 | val pidfile = P.joinDirFile { dir = bootdir, file = "RTPID" } |
138 : | val listfile = P.joinDirFile { dir = bootdir, file = "BOOTLIST" } | ||
139 : | blume | 329 | |
140 : | blume | 361 | val pcmode = PathConfig.new () |
141 : | val _ = PathConfig.processSpecFile (pcmode, pcmodespec) | ||
142 : | blume | 329 | |
143 : | blume | 354 | fun stdpath s = SrcPath.standard pcmode { context = ctxt, spec = s } |
144 : | blume | 352 | |
145 : | val initgspec = stdpath initgspec | ||
146 : | blume | 456 | val maingspec = |
147 : | case root of | ||
148 : | NONE => stdpath maingspec | ||
149 : | blume | 457 | | SOME r => SrcPath.fromDescr pcmode r |
150 : | blume | 352 | |
151 : | blume | 360 | val cmifile = valOf (SrcPath.reAnchoredName (initgspec, bootdir)) |
152 : | handle Option => raise Fail "BootstrapCompile: cmifile" | ||
153 : | |||
154 : | blume | 364 | val fnpolicy = |
155 : | blume | 357 | FilenamePolicy.separate { bindir = bindir, bootdir = bootdir } |
156 : | { arch = arch, os = os } | ||
157 : | |||
158 : | blume | 364 | fun mkParam { primconf, pervasive, pervcorepids } |
159 : | blume | 357 | { corenv } = |
160 : | blume | 349 | { primconf = primconf, |
161 : | fnpolicy = fnpolicy, | ||
162 : | pcmode = pcmode, | ||
163 : | blume | 433 | symval = SSV.symval, |
164 : | blume | 349 | keep_going = keep_going, |
165 : | pervasive = pervasive, | ||
166 : | corenv = corenv, | ||
167 : | pervcorepids = pervcorepids } | ||
168 : | |||
169 : | blume | 327 | val emptydyn = E.dynamicPart E.emptyEnv |
170 : | |||
171 : | (* first, build an initial GeneralParam.info, so we can | ||
172 : | * deal with the pervasive env and friends... *) | ||
173 : | |||
174 : | blume | 360 | val primconf = Primitive.primEnvConf |
175 : | blume | 349 | val mkInitParam = mkParam { primconf = primconf, |
176 : | pervasive = E.emptyEnv, | ||
177 : | blume | 364 | pervcorepids = PidSet.empty } |
178 : | blume | 327 | |
179 : | blume | 349 | val param_nocore = mkInitParam { corenv = BE.staticPart BE.emptyEnv } |
180 : | |||
181 : | blume | 327 | val groupreg = GroupReg.new () |
182 : | val errcons = EM.defaultConsumer () | ||
183 : | blume | 329 | val ginfo_nocore = { param = param_nocore, groupreg = groupreg, |
184 : | errcons = errcons } | ||
185 : | blume | 327 | |
186 : | blume | 449 | fun mk_main_compile arg = let |
187 : | blume | 450 | |
188 : | blume | 335 | val { rts, core, pervasive, primitives, binpaths } = arg |
189 : | blume | 327 | |
190 : | blume | 329 | val ovldR = GenericVC.Control.overloadKW |
191 : | val savedOvld = !ovldR | ||
192 : | val _ = ovldR := true | ||
193 : | blume | 400 | val sbnode = Compile.newSbnodeTraversal () |
194 : | blume | 329 | |
195 : | blume | 327 | (* here we build a new gp -- the one that uses the freshly |
196 : | * brewed pervasive env, core env, and primitives *) | ||
197 : | blume | 398 | val core = valOf (sbnode ginfo_nocore core) |
198 : | blume | 461 | val corenv = CoerceEnv.es2bs (#env (#statenv core ())) |
199 : | blume | 460 | val core_sym = #symenv core () |
200 : | blume | 329 | |
201 : | (* The following is a bit of a hack (but corenv is a hack anyway): | ||
202 : | * As soon as we have core available, we have to patch the | ||
203 : | * ginfo to include the correct corenv (because virtually | ||
204 : | * everybody else needs access to corenv). *) | ||
205 : | blume | 349 | val param_justcore = mkInitParam { corenv = corenv } |
206 : | blume | 329 | val ginfo_justcore = { param = param_justcore, groupreg = groupreg, |
207 : | errcons = errcons } | ||
208 : | |||
209 : | blume | 398 | fun rt n = valOf (sbnode ginfo_justcore n) |
210 : | blume | 327 | val rts = rt rts |
211 : | val pervasive = rt pervasive | ||
212 : | |||
213 : | fun sn2pspec (name, n) = let | ||
214 : | blume | 460 | val { statenv, symenv, statpid, sympid } = rt n |
215 : | blume | 461 | val { env = static, ctxt } = statenv () |
216 : | blume | 327 | val env = |
217 : | blume | 461 | E.mkenv { static = static, |
218 : | blume | 398 | symbolic = symenv (), |
219 : | dynamic = emptydyn } | ||
220 : | blume | 461 | val pidInfo = |
221 : | { statpid = statpid, sympid = sympid, ctxt = ctxt } | ||
222 : | blume | 327 | in |
223 : | { name = name, env = env, pidInfo = pidInfo } | ||
224 : | end | ||
225 : | |||
226 : | val pspecs = map sn2pspec primitives | ||
227 : | |||
228 : | blume | 329 | val _ = ovldR := savedOvld |
229 : | |||
230 : | blume | 372 | (* The following is a hack but must be done for both the symbolic |
231 : | blume | 356 | * and later the dynamic part of the core environment: |
232 : | * we must include these parts in the pervasive env. *) | ||
233 : | blume | 460 | val perv_sym = E.layerSymbolic (#symenv pervasive (), |
234 : | blume | 398 | core_sym) |
235 : | blume | 356 | |
236 : | blume | 349 | val param = |
237 : | mkParam { primconf = Primitive.configuration pspecs, | ||
238 : | blume | 461 | pervasive = |
239 : | E.mkenv { static = #env (#statenv pervasive ()), | ||
240 : | symbolic = perv_sym, | ||
241 : | dynamic = emptydyn }, | ||
242 : | blume | 327 | pervcorepids = |
243 : | PidSet.addList (PidSet.empty, | ||
244 : | blume | 460 | [#statpid pervasive, |
245 : | #sympid pervasive, | ||
246 : | #statpid core]) } | ||
247 : | blume | 349 | { corenv = corenv } |
248 : | blume | 362 | val stab = |
249 : | if deliver then SOME true else NONE | ||
250 : | blume | 327 | in |
251 : | blume | 456 | Servers.dirbase dirbase; |
252 : | blume | 518 | case Parse.parse load_plugin NONE param stab maingspec of |
253 : | blume | 449 | NONE => NONE |
254 : | blume | 399 | | SOME (g, gp) => let |
255 : | blume | 449 | fun thunk () = let |
256 : | blume | 456 | val _ = init_servers g |
257 : | blume | 449 | fun store _ = () |
258 : | val { group = recomp, ... } = | ||
259 : | Compile.newTraversal (fn _ => fn _ => (), store, g) | ||
260 : | blume | 450 | val res = |
261 : | Servers.withServers (fn () => recomp gp) | ||
262 : | blume | 449 | in |
263 : | blume | 450 | if isSome res then let |
264 : | blume | 460 | val rtspid = PS.toHex (#statpid rts) |
265 : | blume | 449 | fun writeList s = let |
266 : | fun add ((p, flag), l) = let | ||
267 : | val n = listName (p, true) | ||
268 : | in | ||
269 : | if flag then n :: l else l | ||
270 : | end | ||
271 : | fun transcribe (p, NONE) = listName (p, true) | ||
272 : | | transcribe (p, SOME (off, desc)) = | ||
273 : | concat [listName (p, false), | ||
274 : | "@", Int.toString off, ":", desc] | ||
275 : | val bootstrings = | ||
276 : | foldr add | ||
277 : | (map transcribe (MkBootList.group g)) | ||
278 : | binpaths | ||
279 : | fun show str = | ||
280 : | (TextIO.output (s, str); | ||
281 : | TextIO.output (s, "\n")) | ||
282 : | blume | 364 | in |
283 : | blume | 449 | app show bootstrings |
284 : | blume | 364 | end |
285 : | blume | 349 | in |
286 : | blume | 449 | if deliver then |
287 : | (SafeIO.perform | ||
288 : | { openIt = fn () => | ||
289 : | AutoDir.openTextOut pidfile, | ||
290 : | closeIt = TextIO.closeOut, | ||
291 : | work = fn s => | ||
292 : | TextIO.output (s, rtspid ^ "\n"), | ||
293 : | blume | 459 | cleanup = fn _ => |
294 : | blume | 449 | OS.FileSys.remove pidfile |
295 : | handle _ => () }; | ||
296 : | SafeIO.perform | ||
297 : | { openIt = fn () => | ||
298 : | AutoDir.openTextOut listfile, | ||
299 : | closeIt = TextIO.closeOut, | ||
300 : | work = writeList, | ||
301 : | blume | 459 | cleanup = fn _ => |
302 : | blume | 449 | OS.FileSys.remove listfile |
303 : | handle _ => () }; | ||
304 : | copyTextFile (SrcPath.osstring initgspec, | ||
305 : | cmifile); | ||
306 : | Say.say ["Runtime System PID is: ", | ||
307 : | rtspid, "\n"]) | ||
308 : | else (); | ||
309 : | true | ||
310 : | blume | 349 | end |
311 : | blume | 449 | else false |
312 : | blume | 349 | end |
313 : | blume | 449 | in |
314 : | blume | 457 | SOME ((g, gp, pcmode), thunk) |
315 : | blume | 399 | end |
316 : | blume | 449 | end handle Option => (Compile.reset (); NONE) |
317 : | blume | 330 | (* to catch valOf failures in "rt" *) |
318 : | blume | 327 | in |
319 : | blume | 329 | case BuildInitDG.build ginfo_nocore initgspec of |
320 : | blume | 449 | SOME x => mk_main_compile x |
321 : | | NONE => NONE | ||
322 : | blume | 327 | end |
323 : | blume | 362 | |
324 : | blume | 449 | fun compile deliver dbopt = |
325 : | blume | 456 | case mk_compile deliver NONE dbopt of |
326 : | blume | 450 | NONE => false |
327 : | blume | 459 | | SOME (_, thunk) => thunk () |
328 : | blume | 449 | |
329 : | local | ||
330 : | blume | 456 | fun slave (dirbase, root) = |
331 : | case mk_compile false (SOME root) (SOME dirbase) of | ||
332 : | blume | 449 | NONE => NONE |
333 : | blume | 457 | | SOME ((g, gp, pcmode), _) => let |
334 : | blume | 449 | val trav = Compile.newSbnodeTraversal () gp |
335 : | fun trav' sbn = isSome (trav sbn) | ||
336 : | in | ||
337 : | blume | 457 | SOME (g, trav', pcmode) |
338 : | blume | 449 | end |
339 : | in | ||
340 : | blume | 452 | val _ = CMBSlaveHook.init archos slave |
341 : | blume | 449 | end |
342 : | |||
343 : | blume | 362 | fun reset () = |
344 : | blume | 398 | (Compile.reset (); |
345 : | blume | 367 | Parse.reset ()) |
346 : | blume | 377 | |
347 : | val make' = compile false | ||
348 : | fun make () = make' NONE | ||
349 : | fun deliver' arg = | ||
350 : | SafeIO.perform { openIt = fn () => (), | ||
351 : | closeIt = reset, | ||
352 : | work = fn () => compile true arg, | ||
353 : | blume | 459 | cleanup = fn _ => () } |
354 : | blume | 377 | fun deliver () = deliver' NONE |
355 : | blume | 434 | val symval = SSV.symval |
356 : | blume | 327 | end |
root@smlnj-gforge.cs.uchicago.edu | ViewVC Help |
Powered by ViewVC 1.0.0 |