1$ ! vms/vmsbuild.com -- compile and link NetHack 3.7.*			[pr]
2$	version_number = "3.7.0"
3$ ! $NHDT-Date: 1609347486 2020/12/30 16:58:06 $  $NHDT-Branch: NetHack-3.7 $:$NHDT-Revision: 1.35 $
4$ ! Copyright (c) 2018 by Robert Patrick Rankin
5$ ! NetHack may be freely redistributed.  See license for details.
6$
7$!TODO: Separate the lua build and create an object library for it instead
8$!	of putting lua modules into nethack.olb.
9$
10$ !
11$ ! usage:
12$ !   $ set default [.src]	!or [-.-.src] if starting from [.sys.vms]
13$ !   $ @[-.sys.vms]vmsbuild  [compiler-option]  [link-option]  [cc-switches] -
14$ !			      [linker-switches]  [interface]
15$ ! options:
16$ !	compiler-option :  either "VAXC", "DECC" or "GNUC" or "" !default VAXC
17$ !	link-option	:  either "SHARE[able]" or "LIB[rary]"	!default SHARE
18$ !	cc-switches	:  optional qualifiers for CC (such as "/noOpt/Debug")
19$ !     linker-switches :  optional qualifers for LINK (/Debug or /noTraceback)
20$ !     interface	:  "TTY" or "CURSES" or "TTY+CURSES" or "CURSES+TTY"
21$ ! notes:
22$ !	If the symbol "CC" is defined, compiler-option is not used (unless it
23$ !	  is "LINK").
24$ !	The link-option refers to VAXCRTL (C Run-Time Library) handling;
25$ !	  to specify it while letting compiler-option default, use "" as
26$ !	  the compiler-option.
27$ !	To re-link without compiling, use "LINK" as special 'compiler-option';
28$ !	  to re-link with GNUC library, 'CC' must begin with "G" (or "g").
29$ !	All options are positional; to specify a later one without an earlier
30$ !	  one, use "" in the earlier one's position, such as
31$ !	$ @[-.sys.vms]vmsbuild "" "" "" "" "TTY+CURSES"
32$
33$	  decc_dflt = f$trnlnm("DECC$CC_DEFAULT")
34$	  j = (decc_dflt.nes."") .and. 1
35$	vaxc_ = "CC" + f$element(j,"#","#/VAXC") + "/NOLIST/OPTIMIZE=NOINLINE"
36$	decc_ = "CC" + f$element(j,"#","#/DECC") + "/PREFIX=ALL/NOLIST"
37$	gnuc_ = "GCC"
38$     if f$type(gcc).eqs."STRING" then  gnuc_ = gcc
39$	gnulib = "gnu_cc:[000000]gcclib/Library"    !(not used w/ vaxc)
40$ ! common CC options (/obj=file doesn't work for GCC 1.36, use rename instead)
41$ !	c_c_  = "/INCLUDE=([-.INCLUDE],[-.LIB.LUA535.SRC])/DEFINE=(""LUA_USE_C89"",""LUA_32BITS"")"
42$	c_c_  = "/INCLUDE=([-.INCLUDE],[-.LIB.LUA535.SRC])/DEFINE=(""LUA_USE_C89"")"
43$	veryold_vms = f$extract(1,1,f$getsyi("VERSION")).eqs."4" -
44		.and. f$extract(3,3,f$getsyi("VERSION")).lts."6"
45$	if veryold_vms then  c_c_ = c_c_ + "/DEFINE=(""VERYOLD_VMS"")"
46$	axp = (f$getsyi("CPU").ge.128)	!f$getsyi("ARCH_NAME").eqs."Alpha"
47$ ! miscellaneous setup
48$	ivqual = %x00038240	!DCL-W-IVQUAL (used to check for ancient vaxc)
49$	abort := exit %x1000002A
50$	cur_dir  = f$environment("DEFAULT")
51$	vmsbuild = f$environment("PROCEDURE")
52$ ! validate first parameter
53$	p1 := 'p1'
54$	if p1.eqs."" .and. (axp .or. decc_dflt.eqs."/DECC") then  p1 = "DECC"
55$	o_VAXC =  0	!(c_opt substring positions)
56$	o_DECC =  5
57$	o_GNUC = 10
58$	o_LINK = 15
59$	o_SPCL = 20
60$	c_opt = f$locate("|"+p1, "|VAXC|DECC|GNUC|LINK|SPECIAL|") !5
61$     if (c_opt/5)*5 .eq. c_opt then  goto p1_ok
62$	copy sys$input: sys$error:	!p1 usage
63%first arg is compiler option; it must be one of
64       "VAXC" -- use VAX C to compile everything
65   or  "DECC" -- use DEC C to compile everything
66   or  "GNUC" -- use GNU C to compile everything
67   or  "LINK" -- skip compilation, just relink nethack.exe
68   or  "SPEC[IAL]" -- just compile and link dlb.exe and recover.exe
69   or    ""   -- default operation (VAXC unless 'CC' is defined)
70
71Note: if a DCL symbol for CC is defined, "VAXC" and "GNUC" are no-ops.
72      If the symbol value begins with "G" (or "g"), then the GNU C
73      library will be included in all link operations.  Do not rebuild
74      dlb+recover with "SPECIAL" unless you have a CC symbol setup with
75      the proper options.
76$	abort
77$p1_ok:
78$ ! validate second parameter
79$	p2 := 'p2'
80$	l_opt = f$locate("|"+p2, "|SHAREABLE|LIBRARY__|NONE_____|") !10
81$     if (l_opt/10)*10 .eq. l_opt then	goto p2_ok
82$	copy sys$input: sys$error:	!p2 usage
83%second arg is C run-time library handling; it must be one of
84       "SHAREABLE" -- link with SYS$SHARE:VAXCRTL.EXE/SHAREABLE
85   or   "LIBRARY"  -- link with SYS$LIBRARY:VAXCRTL.OLB/LIBRARY
86   or    "NONE"    -- explicitly indicate DECC$SHR
87   or      ""      -- default operation (use shareable image)
88
89Note: for MicroVMS 4.x, "SHAREABLE" (which is the default) is required.
90      Specify "NONE" if using DEC C with a CC symbol overriding 1st arg.
91$	abort
92$p2_ok:
93$ ! start from a known location -- [.sys.vms], then move to [-.-.src]
94$	set default 'f$parse(vmsbuild,,,"DEVICE")''f$parse(vmsbuild,,,"DIRECTORY")'
95$	set default [-.-.src]	!move to source directory
96$ ! compiler setup; if a symbol for "CC" is already defined it will be used
97$     if f$type(cc).eqs."STRING" then  goto got_cc
98$	cc = vaxc_			!assume "VAXC" requested or defaulted
99$	if c_opt.eq.o_GNUC then  goto chk_gcc !explicitly invoked w/ "GNUC" option
100$	if c_opt.eq.o_DECC then  cc = decc_
101$	if c_opt.ne.o_VAXC then  goto got_cc !"SPEC" or "LINK", skip compiler check
102$	! we want to prevent function inlining with vaxc v3.x (/opt=noinline)
103$	!   but we can't use noInline with v2.x, so need to determine version
104$	  set noOn
105$	  msgenv = f$environment("MESSAGE")
106$	  set message/noFacil/noSever/noIdent/noText
107$	  cc/noObject _NLA0:/Include=[]     !strip 'noinline' if error
108$	  sts = $status
109$	if sts then  goto reset_msg	!3.0 or later will check out OK
110$	! must be dealing with vaxc 2.x; ancient version (2.2 or earlier)
111$	!   can't handle /include='dir', needs c$include instead
112$	  cc = cc - "=NOINLINE" - ",NOINLINE" - "NOINLINE,"
113$	  if sts.ne.IVQUAL then  goto reset_msg
114$	    define/noLog c$include [-.INCLUDE]
115$	    c_c_ = "/DEFINE=(""ANCIENT_VAXC"")"
116$	    if veryold_vms then  c_c_ = c_c_ - ")" + ",""VERYOLD_VMS"")"
117$reset_msg:
118$	  set message 'msgenv'
119$	  set On
120$	  goto got_cc
121$ !
122$chk_gcc:
123$	cc = gnuc_
124$ ! old versions of gcc-vms don't have <varargs.h> or <stdarg.h> available
125$	  c_c_ = "/DEFINE=(""USE_OLDARGS"")"
126$	  if veryold_vms then  c_c_ = c_c_ - ")" + ",""VERYOLD_VMS"")"
127$	  if veryold_vms then  goto chk_gas	!avoid varargs & stdarg
128$	  if f$search("gnu_cc_include:[000000]varargs.h").nes."" then -
129		c_c_ = "/DEFINE=(""USE_VARARGS"")"
130$	  if f$search("gnu_cc_include:[000000]stdarg.h").nes."" then -
131		c_c_ = "/DEFINE=(""USE_STDARG"")"
132$chk_gas:
133$ ! test whether this version of gas handles the 'const' construct correctly
134$ gas_chk_tmp = "sys$scratch:gcc-gas-chk.tmp"
135$ if f$search(gas_chk_tmp).nes."" then  delete/noconfirm/nolog 'gas_chk_tmp';*
136$ gas_ok = 0	!assume bad
137$ on warning then goto skip_gas
138$ define/user/nolog sys$error 'gas_chk_tmp'
139$ mcr gnu_cc:[000000]gcc-as sys$input: -o _NLA0:
140$DECK
141.const
142.comm dummy,0
143.const
144.comm dummy,0
145$EOD
146$ gas_ok = 1	!assume good
147$ if f$search(gas_chk_tmp).eqs."" then  goto skip_gas
148$ ! if the error file is empty, gas can deal properly with const
149$  gas_ok = f$file_attrib(gas_chk_tmp,"EOF") .eq. 0
150$  delete/noconfirm/nolog 'gas_chk_tmp';*
151$skip_gas:
152$ on warning then continue
153$	  if .not.gas_ok then  c_c_ = c_c_ - ")" + ",""const="")"
154$	  c_c_ = "/INCLUDE=[-.INCLUDE]" + c_c_
155$ !
156$got_cc:
157$	cc = cc + c_c_			!append common qualifiers
158$	if p3.nes."" then  cc = cc + p3 !append optional user preferences
159$	g := 'f$extract(0,1,cc)'
160$	if g.eqs."$" then  g := 'f$extract(1,1,cc)'	!"foreign" gcc
161$	if f$edit(f$extract(1,1,cc),"UPCASE").eqs."E" then  g := X	!GEMC
162$	if g.nes."G" .and. c_opt.ne.o_GNUC then  gnulib = ""
163$ ! linker setup; if a symbol for "LINK" is defined, we'll use it
164$	if f$type(link).nes."STRING" then  link = "LINK/NOMAP"
165$	if p4.nes."" then  link = link + p4 !append optional user preferences
166$	if f$trnlnm("F").nes."" then  close/noLog f
167$	create crtl.opt	!empty
168$	open/Append f crtl.opt
169$	write f "! crtl.opt"
170$   if c_opt.eq.o_DECC .or. l_opt.eq.20
171$   then  $! l_opt=="none", leave crtl.opt empty (shs$share:decc$shr.exe/Share)
172$   else
173$	! gnulib order:  vaxcrtl.exe+gcclib.olb vs gcclib.olb+vaxcrtl.olb
174$	if l_opt.eq.0 then  write f "sys$share:vaxcrtl.exe/Shareable"
175$	if gnulib.nes."" then  write f gnulib
176$	if l_opt.ne.0 then  write f "sys$library:vaxcrtl.olb/Library"
177$   endif
178$	close f
179$	if f$search("crtl.opt;-2").nes."" then  purge/Keep=2/noLog crtl.opt
180$ ! version ID info for linker to record in .EXE files
181$	create ident.opt
182$	open/Append f ident.opt
183$	write f "! ident.opt"
184$	write f "identification=""",version_number,"""	!version"
185$	close f
186$	if f$search("ident.opt;-1").nes."" then  purge/noLog ident.opt
187$ ! final setup
188$	nethacklib = "[-.src]nethack.olb"
189$	create nethack.opt
190! nethack.opt
191nethack.olb/Include=(vmsmain)/Library
192![-.lib.lua]liblua.olb/Library
193! lib$initialize is used to call a routine (before main()) in vmsunix.c that
194! tries to check whether debugger support has been linked in, for PANICTRACE
195sys$library:starlet.olb/Include=(lib$initialize)
196! psect_attr=lib$initialize, Con,Usr,noPic,Rel,Gbl,noShr,noExe,Rd,noWrt,Long
197! IA64 linker doesn't support Usr or Pic and complains that Long is too small
198psect_attr=lib$initialize, Con,Rel,Gbl,noShr,noExe,Rd,noWrt
199! increase memory available to RMS (the default iosegment is probably adequate)
200iosegment=128
201$	if f$search("nethack.opt;-2").nes."" then  purge/Keep=2/noLog nethack.opt
202$	milestone = "write sys$output f$fao("" !5%T "",0),"
203$     if c_opt.eq.o_LINK then  goto link  !"LINK" requested, skip compilation
204$	rename	 := rename/New_Vers
205$	touch	 := set file/Truncate
206$	makedefs := $sys$disk:[-.util]makedefs
207$	show symbol cc
208$	goto begin	!skip subroutines
209$!
210$compile_file:	!input via 'c_file'
211$	no_lib = ( f$extract(0,1,c_file) .eqs. "#" )
212$	if no_lib then	c_file = f$extract(1,255,c_file)
213$	c_name = f$edit(f$parse(c_file,,,"NAME"),"LOWERCASE")
214$	f_opts = ""	!options for this file
215$	if f$type('c_name'_options).nes."" then  f_opts = 'c_name'_options
216$	milestone " (",c_name,")"
217$	if f$search("''c_name'.obj").nes."" then  delete 'c_name'.obj;*
218$	cc 'f_opts' 'c_file'
219$	if .not.no_lib then  nh_obj_list == nh_obj_list + ",''c_name'.obj;0"
220$     return
221$!
222$compile_list:	!input via 'c_list'
223$	nh_obj_list == ""
224$	j = -1
225$ c_loop:
226$	j = j + 1
227$	c_file = f$element(j,",",c_list)  !get next file
228$	if c_file.eqs."," then	goto c_done
229$	c_file = c_file + ".c"
230$	gosub compile_file
231$	goto c_loop
232$ c_done:
233$	nh_obj_list == f$extract(1,999,nh_obj_list)
234$	if nh_obj_list.nes."" then  libr/Obj 'nethacklib' 'nh_obj_list'/Replace
235$	if nh_obj_list.nes."" then  delete 'nh_obj_list'
236$	delete/symbol/global nh_obj_list
237$     return
238$!
239$begin:
240$!
241$! miscellaneous special source file setup
242$!
243$ if f$search("pmatchregex.c").eqs."" then  copy [-.sys.share]pmatchregex.c []*.*
244$ if f$search("random.c").eqs."" then  copy [-.sys.share]random.c []*.*
245$ if f$search("tclib.c") .eqs."" then  copy [-.sys.share]tclib.c  []*.*
246$!
247$	p5 := 'p5'
248$	ttysrc = "[-.win.tty]getline,[-.win.tty]termcap" -
249		+ ",[-.win.tty]topl,[-.win.tty]wintty"
250$	cursessrc = "[-.win.curses]cursdial,[-.win/curses]cursmesg" -
251		+ ",[-.win.curses]cursinit,[-.win.curses]cursmisc" -
252		+ ",[-.win.curses]cursinvt,[-.win.curses]cursstat" -
253		+ ",[-.win.curses]cursmain,[-.win.curses]curswins"
254$	interface = ttysrc !default
255$	if p5.eqs."CURSES" then  interface = cursessrc
256$	if p5.eqs."TTY+CURSES" then  interface = ttysrc + "," + cursessrc
257$	if p5.eqs."CURSES+TTY" then  interface = cursessrc + "," + ttysrc
258$
259$ if f$search("[-.include]nhlua.h").eqs.""
260$ then
261$	create [-.include]nhlua.h	!empty
262$       set file/att=(RFM:STM) [-.include]nhlua.h
263$	open/Append f [-.include]nhlua.h
264$       write f "/* nhlua.h - generated by vmsbuild.com */"
265$       write f "#include ""[-.lib.lua535.src]lua.h"""
266$       write f "LUA_API int (lua_error) (lua_State *L) NORETURN;"
267$       write f "#include ""[-.lib.lua535.src]lualib.h"""
268$       write f "#include ""[-.lib.lua535.src]lauxlib.h"""
269$       write f "/*nhlua.h*/"
270$	close f
271$ endif
272$!
273$! create object library
274$!
275$     if c_opt.ne.o_SPCL .or. f$search(nethacklib).eqs."" then -
276  libr/Obj 'nethacklib'/Create=(Block=3000,Hist=0)
277$ if f$search("''nethacklib';-1").nes."" then  purge 'nethacklib'
278$!
279$! compile and link makedefs, then nethack, dlb+recover.
280$!
281$ milestone "<compiling...>"
282$ c_list = "[-.sys.vms]vmsmisc,[-.sys.vms]vmsfiles,[]alloc,dlb,monst,objects"
283$     if c_opt.eq.o_SPCL then  c_list = c_list + ",decl,drawing"
284$ gosub compile_list
285$     if c_opt.eq.o_SPCL then  goto special !"SPECIAL" requested, skip main build
286$ set default [-.util]
287$ c_list = "#makedefs"
288$ gosub compile_list
289$ link makedefs.obj,'nethacklib'/Lib,[-.src]ident.opt/Opt,[-.src]crtl/Opt
290$ milestone "makedefs"
291$! create some build-time files
292$ makedefs -p	!pm.h
293$ makedefs -o	!onames.h
294$ makedefs -v	!date.h
295$ milestone " (*.c)"
296$ set default [-.src]
297$! compile most of the source files:
298$ c_list = "decl,version,[-.sys.vms]vmsmain,[-.sys.vms]vmsunix" -
299	+ ",[-.sys.vms]vmstty,[-.sys.vms]vmsmail" -
300	+ ",[]isaac64" -			!already in [.src]
301	+ ",[]random,[]tclib,[]pmatchregex"	!copied from [-.sys.share]
302$ gosub compile_list
303$ c_list = interface !ttysrc or cursessrc or both
304$ gosub compile_list
305$ c_list = "allmain,apply,artifact,attrib,ball,bones,botl,cmd,dbridge" -
306	+ ",dothrow,drawing,detect,dig,display,do,do_name,do_wear,dog" -
307	+ ",dogmove,dokick,dungeon,eat,end,engrave,exper,explode" -
308	+ ",files,fountain"
309$ gosub compile_list
310$ c_list = "hack,hacklib,insight,invent,light,lock,mail,makemon" -
311	+ ",mcastu,mhitm,mhitu,minion,mklev,mkmap,mkmaze" -
312	+ ",mkobj,mkroom,mon,mondata,monmove,mplayer,mthrowu,muse" -
313	+ ",music,o_init,objnam,options,pager,pickup"
314$ gosub compile_list
315$ c_list = "pline,polyself,potion,pray,priest,quest,questpgr,read" -
316	+ ",rect,region,restore,rip,rnd,role,rumors,save,sfstruct,shk" -
317	+ ",shknam,sit,sounds,sp_lev,spell,steal,steed,sys,teleport" -
318	+ ",timeout,topten,track,trap,u_init"
319$ gosub compile_list
320$ c_list = "uhitm,vault,vision,weapon,were,wield,windows" -
321	+ ",wizard,worm,worn,write,zap"
322$ gosub compile_list
323$!
324$! Files added in 3.7
325$!
326$ c_list = "nhlua,nhlobj,nhlsel"
327$ gosub compile_list
328$!
329$! 3.7 runtime LUA level parser/loader
330$!
331$ c_list = "[-.lib.lua535.src]lapi,[-.lib.lua535.src]lauxlib,[-.lib.lua535.src]lbaselib" -
332	+ ",[-.lib.lua535.src]lbitlib,[-.lib.lua535.src]lcode,[-.lib.lua535.src]lcorolib" -
333	+ ",[-.lib.lua535.src]lctype,[-.lib.lua535.src]ldblib,[-.lib.lua535.src]ldebug" -
334	+ ",[-.lib.lua535.src]ldo,[-.lib.lua535.src]ldump,[-.lib.lua535.src]lfunc" -
335	+ ",[-.lib.lua535.src]lgc,[-.lib.lua535.src]linit,[-.lib.lua535.src]liolib" -
336	+ ",[-.lib.lua535.src]llex"
337$ gosub compile_list
338$ c_list = "[-.lib.lua535.src]lmathlib,[-.lib.lua535.src]lmem,[-.lib.lua535.src]loadlib" -
339	+ ",[-.lib.lua535.src]lobject,[-.lib.lua535.src]lopcodes,[-.lib.lua535.src]loslib" -
340	+ ",[-.lib.lua535.src]lparser,[-.lib.lua535.src]lstate,[-.lib.lua535.src]lstring" -
341	+ ",[-.lib.lua535.src]lstrlib,[-.lib.lua535.src]ltable,[-.lib.lua535.src]ltablib" -
342	+ ",[-.lib.lua535.src]ltm,[-.lib.lua535.src]lundump,[-.lib.lua535.src]lutf8lib" -
343	+ ",[-.lib.lua535.src]lvm,[-.lib.lua535.src]lzio"
344$ gosub compile_list
345$!
346$link:
347$ milestone "<linking...>"
348$ link/Exe=nethack.exe nethack.opt/Options,ident.opt/Options,crtl.opt/Options
349$ milestone "NetHack"
350$     if c_opt.eq.o_LINK then  goto done	!"LINK" only
351$special:
352$!
353$! utilities only [dgn_comp and lev_comp are gone]
354$!
355$ set default [-.util]
356$ c_list = "#panic,#dlb_main,#recover"
357$ gosub compile_list
358$ link/exe=dlb.exe dlb_main.obj,-
359	panic.obj,'nethacklib'/Lib,[-.src]ident.opt/Opt,[-.src]crtl.opt/Opt
360$ milestone "dlb"
361$ link/exe=recover.exe recover.obj,-
362	'nethacklib'/Lib,[-.src]ident.opt/Opt,[-.src]crtl.opt/Opt
363$ milestone "recover"
364$!
365$done:
366$	set default 'cur_dir'
367$ exit
368