source: trunk/third/gcc/make-cc1.com @ 11288

Revision 11288, 16.6 KB checked in by ghudson, 26 years ago (diff)
This commit was generated by cvs2svn to compensate for changes in r11287, which included commits to RCS files with non-trunk default branches.
Line 
1$v='f$verify(0) !make-cc1.com
2$!
3$!      Build the GNU C compiler on VMS.
4$!
5$!      Usage:
6$!        $ @make-cc1.com [host-compiler] [various]
7$!
8$!      where [host-compiler] is one of "GNUC", "VAXC", "DECC";
9$!      default when none specified is "GNUC",
10$!      and where [various] is one or more of "CC1", "CC1PLUS",
11$!      "CC1OBJ", "OBJCLIB", "INDEPENDENT", "BC", "ALL", "LINK", "DEBUG".
12$!      "CC1" (C compiler) is the default; of the others, only
13$!      "CC1PLUS" (C++ compiler), "CC1OBJ" (Objective-C compiler),
14$!      and "OBJCLIB" (Objective-C run-time library) are of interest
15$!      for normal installation.
16$!      If both [host-compiler] and other option(s) are specified,
17$!      the host compiler argument must come first.
18$!
19$ if f$type(gcc_debug).eqs."INTEGER" then  if gcc_debug.and.1 then  set verify
20$
21$ p1 = f$edit(p1,"UPCASE,TRIM")
22$ if p1.eqs."" then  p1 = "GNUC"
23$!
24$!      Compiler-specific setup (assume GNU C, then override as necessary):
25$!
26$ CC     = "gcc"
27$ CFLAGS = "/Opt=2/Debug/noVerbos/CC1=""-mpcc-alignment"""
28$ LIBS   = "gnu_cc:[000000]gcclib.olb/Libr,sys$library:vaxcrtl.olb/Libr"
29$ if p1.eqs."GNUC"
30$ then
31$   p1 = ""
32$ else
33$   CC     = "cc"
34$   CFLAGS = "/noOpt"   !disable optimizer when bootstrapping with native cc
35$   if p2.eqs."DEBUG" .or. p3.eqs."DEBUG" then  CFLAGS = CFLAGS + "/Debug"
36$   if p1.eqs."VAXC"
37$   then
38$     p1 = ""
39$     if f$trnlnm("DECC$CC_DEFAULT").nes."" then  CC = "cc/VAXC"
40$     LIBS = "alloca.obj,sys$library:vaxcrtl.olb/Libr"
41$     define/noLog SYS SYS$LIBRARY:
42$   else
43$     if p1.eqs."DECC"
44$     then
45$       p1 = ""
46$       if f$trnlnm("DECC$CC_DEFAULT").nes."" then  CC = "cc/DECC"
47$       CC = CC + "/Prefix=All/Warn=Disabl=(ImplicitFunc)"
48$       LIBS = "alloca.obj"     !DECC$SHR will be found implicitly by linker
49$       define/noLog SYS DECC$LIBRARY_INCLUDE:
50$     endif !DECC
51$   endif !VAXC
52$ endif !GNUC
53$
54$!
55$!      Other setup:
56$!
57$ LDFLAGS =     "/noMap"
58$ PARSER  =     "bison"
59$ PARSER_FLAGS= "/Define/Verbose"
60$ RENAME  =     "rename/New_Version"
61$ LINK    =     "link"
62$ EDIT    =     "edit"
63$ SEARCH  =     "search"
64$ ABORT   =     "exit %x002C"
65$ echo    =     "write sys$output"
66$!
67$!      Stage[123] options
68$!
69$ CINCL1 =      "/Incl=[]"                      !stage 1 -I flags
70$ CINCL2 =      "/Incl=([],[.ginclude])"        !stage 2,3,... flags
71$ CINCL_SUB =   "/Incl=([],[-],[-.ginclude])"   ![.cp] flags
72$
73$!!!!!!!
74$!      Nothing beyond this point should need any local configuration changes.
75$!!!!!!!
76$
77$! Set the default directory to the same place as this command procedure.
78$ flnm = f$enviroment("PROCEDURE")      !get current procedure name
79$ set default 'f$parse(flnm,,,"DEVICE")''f$parse(flnm,,,"DIRECTORY")'
80$
81$!
82$!  First we figure out what needs to be done.  This is sort of like a limited
83$! make facility - the command line options specify exactly what components
84$! we want to build.  The following options are understood:
85$!
86$!      LINK:   Assume that the object modules for the selected compiler(s)
87$!              have already been compiled, perform link phase only.
88$!
89$!      CC1:    Compile and link "C" compiler.
90$!
91$!      CC1PLUS:Compile and link "C++" compiler.
92$!
93$!      CC1OBJ: Compile and link objective C compiler.
94$!
95$!      ALL:    Compile and link all of the CC1 passes.
96$!
97$!      INDEPENDENT:
98$!              Compile language independent source modules. (On by default).
99$!
100$!      BC:
101$!              Compile byte compiler source modules. (On by default).
102$!
103$!      OBJCLIB:
104$!              Compile Objective-C run-time library.
105$!
106$!      DEBUG:  Link images with /debug.
107$!
108$! If you want to list more than one option, you should use a spaces to
109$! separate them.
110$!
111$!      Any one of the above options can be prefaced with a "NO".  For example,
112$! if you had already built GCC, and you wanted to build G++, you could use the
113$! "CC1PLUS NOINDEPENDENT" options, which would only compile the C++ language
114$! specific source files, and then link the C++ compiler.
115$!
116$! If you do not specify which compiler you want to build, it is assumed that
117$! you want to build GNU-C ("CC1").
118$!
119$! Now figure out what we have been requested to do.
120$p1 = p1+" "+p2+" "+p3+" "+p4+" "+p5+" "+p6+" "+p7+" "+p8
121$p1 = f$edit(p1,"COMPRESS,TRIM")
122$i=0
123$DO_ALL = 0
124$DO_LINK = 0
125$DO_DEBUG = 0
126$DO_CC1PLUS = 0
127$DO_CC1OBJ = 0
128$DO_OBJCLIB = 0
129$if f$trnlnm("cfile$").nes."" then  close/noLog cfile$
130$open cfile$ compilers.list
131$cinit:read cfile$ compilername/end=cinit_done
132$DO_'compilername'=0
133$goto cinit
134$cinit_done: close cfile$
135$DO_INDEPENDENT = 1
136$DO_DEFAULT = 1
137$DO_BC = 1
138$loop:
139$string = f$element(i," ",p1)
140$if string.eqs." " then goto done
141$flag = 1
142$if string.eqs."CC1PLUS" then DO_DEFAULT = 0
143$if string.eqs."CC1OBJ" then DO_DEFAULT = 0
144$if string.eqs."OBJCLIB"
145$then   DO_DEFAULT = 0
146$       DO_INDEPENDENT = DO_CC1OBJ
147$       DO_BC = DO_CC1OBJ
148$endif
149$if f$extract(0,2,string).nes."NO" then goto parse_option
150$  string=f$extract(2,f$length(string)-2,string)
151$  flag = 0
152$parse_option:
153$DO_'string' = flag
154$i=i+1
155$goto loop
156$!
157$done:
158$if DO_DEFAULT.eq.1 then DO_CC1 = 1
159$echo "This command file will now perform the following actions:
160$if DO_LINK.eq.1 then goto link_only
161$if DO_ALL.eq.1 then echo "   Compile all language specific object modules."
162$if DO_CC1.eq.1 then echo "   Compile C specific object modules."
163$if DO_CC1PLUS.eq.1 then echo "   Compile C++ specific object modules."
164$if DO_CC1OBJ.eq.1 then echo "   Compile obj-C specific object modules."
165$if DO_INDEPENDENT.eq.1 then echo "   Compile language independent object modules."
166$if DO_BC.eq.1 then echo "   Compile byte compiler object modules."
167$if DO_OBJCLIB.eq.1 then echo "   Create Objective-C run-time library."
168$link_only:
169$if DO_CC1.eq.1 then    echo "   Link C compiler (gcc-cc1.exe)."
170$if DO_CC1PLUS.eq.1 then echo "   Link C++ compiler (gcc-cc1plus.exe)."
171$if DO_CC1OBJ.eq.1 then echo "   Link objective-C compiler (gcc-cc1obj.exe)."
172$if DO_DEBUG.eq.1 then echo  "   Link images to run under debugger."
173$!
174$! Update CFLAGS with appropriate CINCLx value.
175$!
176$if f$edit(f$extract(0,3,CC),"LOWERCASE").nes."gcc" then goto stage1
177$if f$search("gcc-cc1.exe").eqs."" then goto stage1
178$if f$file_attr("gnu_cc:[000000]gcc-cc1.exe","FID").nes.-
179    f$file_attr("gcc-cc1.exe","FID") then goto stage1
180$ CFLAGS = CFLAGS + CINCL2
181$ goto cinclX
182$stage1:
183$ CFLAGS = CFLAGS + CINCL1
184$cinclX:
185$!
186$! Test and see if we need these messages or not.  The -1 switch gives it away.
187$!
188$gas := $gnu_cc:[000000]gcc-as.exe
189$if f$search(gas-"$").eqs."" then  goto gas_missing_message     !must be VAXC
190$define/user sys$error sys$scratch:gas_test.tmp
191$gas -1 nla0: -o nla0:
192$size=f$file_attributes("sys$scratch:gas_test.tmp","ALQ")
193$delete/nolog sys$scratch:gas_test.tmp;*
194$if size.eq.0 then goto skip_gas_message
195$type sys$input:        !an old version of gas was found
196
197-----
198     Note:  you appear to have an old version of gas, the GNU assembler.
199GCC 2.x treats external variables differently than GCC 1.x does.  Before
200you use GCC 2.x, you should obtain a version of the assembler which works
201with GCC 2.x (gas-1.38 and earlier did not have the necessary support;
202gas-2.0 through gas-2.3 did not work reliably for vax/vms configuration).
203The assembler in gcc-vms-1.42 contained patches to provide the proper
204support, and more recent versions have an up to date version of gas which
205provides the support.  gas from binutils-2.5 or later is recommended.
206
207     If you do not update the assembler, the compiler will still work,
208but `extern const' variables will be treated as `extern'.  This will result
209in linker warning messages about mismatched psect attributes, and these
210variables will be placed in read/write storage.
211-----
212
213$goto skip_gas_message
214$gas_missing_message:
215$type sys$input:        !no version of gas was found
216
217-----
218     Note:  you appear to be missing gas, the GNU assembler.  Since
219GCC produces assembly code as output from compilation, you need the
220assembler to make full use of the compiler.  It should be put in place
221as GNU_CC:[000000]GCC-AS.EXE.
222
223     A prebuilt copy of gas is available from the "gcc-vms" distribution,
224and the gas source code is included in the GNU "binutils" distribution.
225Version 2.5.2 or later is recommended.
226-----
227
228$skip_gas_message:
229$!
230$!
231$ if DO_DEBUG.eq.1 then LDFLAGS = LDFLAGS + "/Debug"
232$!
233$if DO_LINK.eq.1 then goto no_yfiles    !compile_cc1
234$!
235$! Build alloca if necessary (in 'LIBS for use with VAXC)
236$!
237$ if f$locate("alloca.obj",f$edit(LIBS,"lowercase")).ge.f$length(LIBS) then -
238        goto skip_alloca
239$ if f$search("alloca.obj").nes."" then -  !does .obj exist? is it up to date?
240    if f$cvtime(f$file_attributes("alloca.obj","RDT")).gts.-
241       f$cvtime(f$file_attributes("alloca.c","RDT")) then  goto skip_alloca
242$set verify
243$ 'CC''CFLAGS'/Defi=("HAVE_CONFIG_H","STACK_DIRECTION=(-1)") alloca.c
244$!'f$verify(0)
245$skip_alloca:
246$!
247$if DO_BC.eq.1
248$       then
249$       call compile bi_all.opt ""
250$       if f$trnlnm("ifile$").nes."" then  close/noLog ifile$
251$       open ifile$ bc_all.list
252$       read ifile$ bc_line
253$       close ifile$
254$       bc_index = 0
255$bc_loop:
256$       tfile = f$element(bc_index, ",", bc_line)
257$       if tfile.eqs."," then goto bc_done
258$       call bc_generate 'tfile' "bi_all.opt/opt,"
259$       bc_index = bc_index + 1
260$       goto bc_loop
261$bc_done:
262$       endif
263$!
264$!
265$if DO_INDEPENDENT.eq.1
266$       then
267$!
268$! First build a couple of header files from the machine description
269$! These are used by many of the source modules, so we build them now.
270$!
271$set verify
272$ 'CC''CFLAGS' rtl.c
273$ 'CC''CFLAGS' obstack.c
274$!'f$verify(0)
275$! Generate insn-attr.h
276$       call generate insn-attr.h
277$       call generate insn-flags.h
278$       call generate insn-codes.h
279$       call generate insn-config.h
280$!
281$call compile independent.opt "rtl,obstack,insn-attrtab"
282$!
283$       call generate insn-attrtab.c "rtlanal.obj,"
284$set verify
285$ 'CC''CFLAGS' insn-attrtab.c
286$ 'CC''CFLAGS' bc-emit.c
287$ 'CC''CFLAGS' bc-optab.c
288$!'f$verify(0)
289$       endif
290$!
291$compile_cc1:
292$if (DO_CC1 + DO_CC1OBJ) .ne.0
293$       then
294$if (f$search("C-PARSE.Y") .eqs. "") then goto yes_yfiles
295$if (f$cvtime(f$file_attributes("C-PARSE.IN","RDT")).gts. -
296            f$cvtime(f$file_attributes("C-PARSE.Y","RDT")))  -
297                then goto yes_yfiles
298$if f$parse("[.OBJC]").eqs."" then create/Directory [.objc]
299$if (f$search("[.OBJC]OBJC-PARSE.Y") .eqs. "") then goto yes_yfiles
300$if (f$cvtime(f$file_attributes("C-PARSE.IN","RDT")).gts. -
301            f$cvtime(f$file_attributes("[.OBJC]OBJC-PARSE.Y","RDT")))  -
302                then goto yes_yfiles
303$GOTO no_yfiles
304$yes_yfiles:
305$echo "Now processing c-parse.in to generate c-parse.y and [.objc]objc-parse.y."
306$ EDIT/Tpu/noJournal/noSection/noDisplay/Command=sys$input:
307!
308!     Read c-parse.in, write c-parse.y and objc/objc-parse.y, depending on
309!     paired lines of "ifc" & "end ifc" and "ifobjc" & "end ifobjc" to
310!     control what goes into each file.  Most lines will be common to
311!     both (hence not bracketed by either control pair).  Mismatched
312!     pairs aren't detected--garbage in, garbage out...
313!
314
315   PROCEDURE do_output()
316      IF NOT objc_only THEN POSITION(END_OF(c)); COPY_TEXT(input_line); ENDIF;
317      IF NOT c_only THEN POSITION(END_OF(objc)); COPY_TEXT(input_line); ENDIF;
318      POSITION(input_file);                     !reset
319   ENDPROCEDURE;
320
321   input_file := CREATE_BUFFER("input", "c-parse.in");  !load data
322                 SET(NO_WRITE, input_file);
323   c          := CREATE_BUFFER("c_output");     !1st output file
324   objc       := CREATE_BUFFER("objc_output");  !2nd output file
325
326   POSITION(BEGINNING_OF(input_file));
327   c_only     := 0;
328   objc_only  := 0;
329
330   LOOP
331      EXITIF MARK(NONE) = END_OF(input_file);   !are we done yet?
332
333      input_line := CURRENT_LINE;               !access current_line just once
334      CASE EDIT(input_line, TRIM_TRAILING, OFF, NOT_IN_PLACE)
335         ["ifc"]        : c_only := 1;
336         ["end ifc"]    : c_only := 0;
337         ["ifobjc"]     : objc_only := 1;
338         ["end ifobjc"] : objc_only := 0;
339!         default -- add non-control line to either or both output files
340         [INRANGE]      : do_output();          !between "end" and "if"
341         [OUTRANGE]     : do_output();          !before "end" or after "if"
342      ENDCASE;
343
344      MOVE_VERTICAL(1);                         !go to next line
345   ENDLOOP;
346
347   WRITE_FILE(c, "c-parse.y");
348   WRITE_FILE(objc, "[.objc]objc-parse.y");
349   QUIT
350$       endif   
351$no_yfiles:
352$!
353$open cfile$ compilers.list
354$cloop:read cfile$ compilername/end=cdone
355$! language specific modules
356$!
357$if (DO_ALL + DO_'compilername').eq.0 then goto cloop
358$if DO_LINK.eq.0 then -
359 call compile 'compilername'-objs.opt "obstack,bc-emit,bc-optab"
360$!
361$! CAUTION: If you want to link gcc-cc1* to the sharable image library
362$! VAXCRTL, see the notes in gcc.texinfo (or INSTALL) first.
363$!
364$set verify
365$ 'LINK''LDFLAGS'/Exe=gcc-'compilername'.exe  version.opt/Opt,-
366          'compilername'-objs.opt/Opt,independent.opt/Opt,-
367          'LIBS'
368$!'f$verify(0)
369$goto cloop
370$!
371$!
372$cdone: close cfile$
373$!
374$ if DO_OBJCLIB
375$ then  set default [.objc]     !push
376$       save_cflags = CFLAGS
377$       CFLAGS = CFLAGS - CINCL1 - CINCL2 + CINCL_SUB
378$       MFLAGS = "/Lang=ObjC" + CFLAGS
379$       library/Obj [-]objclib.olb/Create
380$       if f$trnlnm("IFILE$").nes."" then  close/noLog ifile$
381$       open/Read ifile$ [-]objc-objs.opt
382$ocl1:  read/End=ocl3 ifile$ line
383$       i = 0
384$ocl2:  o = f$element(i,",",line)
385$       if o.eqs."," then goto ocl1
386$       n = o - ".o"
387$       if f$search(n + ".m").nes.""
388$       then    f = n + ".m"
389$               flags = MFLAGS
390$       else    f = n + ".c"
391$               flags = CFLAGS
392$       endif
393$       set verify
394$ 'CC' 'flags' 'f'
395$!'f$verify(0)'
396$       library/Obj [-]objclib.olb 'n'.obj/Insert
397$       delete/noConfirm/noLog 'n'.obj;*
398$       i = i + 1
399$       goto ocl2
400$ocl3:  close ifile$
401$       CFLAGS = save_cflags
402$       set default [-] !pop
403$ endif !DO_OBJCLIB
404$!
405$!      Done
406$!
407$! 'f$verify(v)
408$exit
409$!
410$!  Various DCL subroutines follow...
411$!
412$!  This routine takes parameter p1 to be a linker options file with a list
413$!  of object files that are needed.  It extracts the names, and compiles
414$!  each source module, one by one.  File names that begin with an
415$!  "INSN-" are assumed to be generated by a GEN*.C program.
416$!
417$!  Parameter P2 is a list of files which will appear in the options file
418$!  that should not be compiled.  This allows us to handle special cases.
419$!
420$compile:
421$subroutine
422$on error then goto c_err
423$on control_y then goto c_err
424$open ifile$ 'p1'
425$loop: read ifile$ line/end=c_done
426$!
427$i=0
428$loop1:
429$flnm=f$element(i,",",line)
430$i=i+1
431$if flnm.eqs."" then goto loop
432$if flnm.eqs."," then goto loop
433$if f$locate(flnm,p2).lt.f$length(p2) then goto loop1
434$! check for front-end subdirectory: "[.prfx]flnm"
435$prfx = ""
436$k = f$locate("]",flnm)
437$if k.eq.1      ![]c-common for [.cp]
438$then
439$ if f$search(f$parse(".obj",flnm)).nes."" then  goto loop1
440$ flnm = f$extract(2,999,flnm)
441$else if k.lt.f$length(flnm)
442$ then  prfx = f$extract(2,k-2,flnm)
443$       flnm = f$extract(k+1,99,flnm)
444$ endif
445$endif
446$ if prfx.nes.""
447$ then  set default [.'prfx']   !push
448$       save_cflags = CFLAGS
449$       CFLAGS = CFLAGS - CINCL1 - CINCL2 + CINCL_SUB
450$ endif
451$!
452$ if f$locate("parse",flnm).nes.f$length(flnm)
453$ then
454$   if f$search("''flnm'.c").nes."" then -
455      if f$cvtime(f$file_attributes("''flnm'.c","RDT")).ges. -
456         f$cvtime(f$file_attributes("''flnm'.y","RDT")) then  goto skip_yacc
457$ set verify
458$       'PARSER' 'PARSER_FLAGS' 'flnm'.y
459$       'RENAME' 'flnm'_tab.c 'flnm'.c
460$       'RENAME' 'flnm'_tab.h 'flnm'.h
461$!'f$verify(0)
462$       if flnm.eqs."cp-parse" .or. (prfx.eqs."cp" .and. flnm.eqs."parse")
463$       then            ! fgrep '#define YYEMPTY' cp-parse.c >>cp-parse.h
464$               if f$trnlnm("JFILE$").nes."" then  close/noLog jfile$
465$               open/Append jfile$ 'flnm'.h
466$               'SEARCH'/Exact/Output=jfile$ 'flnm'.c "#define YYEMPTY"
467$               close jfile$
468$       endif
469$skip_yacc:
470$        echo " (Ignore any warning about not finding file ""bison.simple"".)"
471$ endif
472$!
473$if f$extract(0,5,flnm).eqs."insn-" then call generate 'flnm'.c
474$!
475$set verify
476$ 'CC''CFLAGS' 'flnm'.c
477$!'f$verify(0)
478$ if prfx.nes.""
479$ then  set default [-]         !pop
480$       CFLAGS = save_CFLAGS
481$ endif
482$
483$goto loop1
484$!
485$!
486$! In case of error or abort, go here (In order to close file).
487$!
488$c_err: !'f$verify(0)
489$close ifile$
490$ABORT
491$!
492$c_done:
493$close ifile$
494$endsubroutine
495$!
496$! This subroutine generates the insn-* files.  The first argument is the
497$! name of the insn-* file to generate.  The second argument contains a
498$! list of any other object modules which must be linked to the gen*.c
499$! program.
500$!
501$generate:
502$subroutine
503$if f$extract(0,5,p1).nes."INSN-"
504$       then
505$       write sys$error "Unknown file passed to generate."
506$       ABORT
507$       endif
508$root1=f$parse(f$extract(5,255,p1),,,"NAME")
509$       set verify
510$ 'CC''CFLAGS' GEN'root1'.C
511$ 'LINK''f$string(LDFLAGS - "/Debug")' GEN'root1'.OBJ,rtl.obj,obstack.obj,'p2' -
512          'LIBS'
513$!      'f$verify(0)
514$!
515$set verify
516$       assign/user 'p1' sys$output:
517$       mcr sys$disk:[]GEN'root1' vax.md
518$!'f$verify(0)
519$endsubroutine
520$!
521$! This subroutine generates the bc-* files.  The first argument is the
522$! name of the bc-* file to generate.  The second argument contains a
523$! list of any other object modules which must be linked to the bi*.c
524$! program.
525$!
526$bc_generate:
527$subroutine
528$if f$extract(0,3,p1).nes."BC-"
529$       then
530$       write sys$error "Unknown file passed to bc_generate."
531$       ABORT
532$       endif
533$root1=f$parse(f$extract(3,255,p1),,,"NAME")
534$       set verify
535$ 'CC''CFLAGS' BI-'root1'.C
536$ 'LINK''f$string(LDFLAGS - "/Debug")' BI-'root1'.OBJ,'p2' -
537          'LIBS'
538$!      'f$verify(0)
539$!
540$set verify
541$       assign/user bytecode.def sys$input:
542$       assign/user 'p1' sys$output:
543$       mcr sys$disk:[]BI-'root1'
544$!'f$verify(0)
545$endsubroutine
Note: See TracBrowser for help on using the repository browser.