xref: /freebsd/sys/tools/makesyscalls.lua (revision 1719886f)
1--
2-- SPDX-License-Identifier: BSD-2-Clause
3--
4-- Copyright (c) 2019 Kyle Evans <kevans@FreeBSD.org>
5--
6-- Redistribution and use in source and binary forms, with or without
7-- modification, are permitted provided that the following conditions
8-- are met:
9-- 1. Redistributions of source code must retain the above copyright
10--    notice, this list of conditions and the following disclaimer.
11-- 2. Redistributions in binary form must reproduce the above copyright
12--    notice, this list of conditions and the following disclaimer in the
13--    documentation and/or other materials provided with the distribution.
14--
15-- THIS SOFTWARE IS PROVIDED BY THE AUTHOR AND CONTRIBUTORS ``AS IS'' AND
16-- ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE
17-- IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE
18-- ARE DISCLAIMED.  IN NO EVENT SHALL THE AUTHOR OR CONTRIBUTORS BE LIABLE
19-- FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL
20-- DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS
21-- OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION)
22-- HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
23-- LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY
24-- OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF
25-- SUCH DAMAGE.
26--
27
28
29-- We generally assume that this script will be run by flua, however we've
30-- carefully crafted modules for it that mimic interfaces provided by modules
31-- available in ports.  Currently, this script is compatible with lua from ports
32-- along with the compatible luafilesystem and lua-posix modules.
33local lfs = require("lfs")
34local unistd = require("posix.unistd")
35
36local savesyscall = -1
37local maxsyscall = -1
38local structs = {}
39local generated_tag = "@" .. "generated"
40
41-- Default configuration; any of these may get replaced by a configuration file
42-- optionally specified.
43local config = {
44	os_id_keyword = "FreeBSD",		-- obsolete, ignored on input, not generated
45	abi_func_prefix = "",
46	libsysmap = "/dev/null",
47	libsys_h = "/dev/null",
48	sysnames = "syscalls.c",
49	sysproto = "../sys/sysproto.h",
50	sysproto_h = "_SYS_SYSPROTO_H_",
51	syshdr = "../sys/syscall.h",
52	sysmk = "/dev/null",
53	syssw = "init_sysent.c",
54	syscallprefix = "SYS_",
55	switchname = "sysent",
56	namesname = "syscallnames",
57	systrace = "systrace_args.c",
58	capabilities_conf = "capabilities.conf",
59	capenabled = {},
60	compat_set = "native",
61	mincompat = 0,
62	abi_type_suffix = "",
63	abi_flags = "",
64	abi_flags_mask = 0,
65	abi_headers = "",
66	abi_intptr_t = "intptr_t",
67	abi_size_t = "size_t",
68	abi_u_long = "u_long",
69	abi_long = "long",
70	abi_semid_t = "semid_t",
71	abi_ptr_array_t = "",
72	ptr_intptr_t_cast = "intptr_t",
73	syscall_abi_change = "",
74	sys_abi_change = {},
75	syscall_no_abi_change = "",
76	sys_no_abi_change = {},
77	obsol = "",
78	obsol_dict = {},
79	unimpl = "",
80	unimpl_dict = {},
81}
82
83local config_modified = {}
84local cleantmp = true
85local tmpspace = "/tmp/sysent." .. unistd.getpid() .. "/"
86
87local output_files = {
88	"sysnames",
89	"syshdr",
90	"sysmk",
91	"libsysmap",
92	"libsys_h",
93	"syssw",
94	"systrace",
95	"sysproto",
96}
97
98-- These ones we'll create temporary files for; generation purposes.
99local temp_files = {
100	"libsys_h_type",
101	"libsys_h_func",
102	"sysaue",
103	"sysdcl",
104	"syscompat",
105	"syscompatdcl",
106	"sysent",
107	"sysinc",
108	"sysarg",
109	"sysprotoend",
110	"systracetmp",
111	"systraceret",
112}
113
114-- Opened files
115local files = {}
116
117local function cleanup()
118	for _, v in pairs(files) do
119		assert(v:close())
120	end
121	if cleantmp then
122		if lfs.dir(tmpspace) then
123			for fname in lfs.dir(tmpspace) do
124				if fname ~= "." and fname ~= ".." then
125					assert(os.remove(tmpspace .. "/" ..
126					    fname))
127				end
128			end
129		end
130
131		if lfs.attributes(tmpspace) and not lfs.rmdir(tmpspace) then
132			assert(io.stderr:write("Failed to clean up tmpdir: " ..
133			    tmpspace .. "\n"))
134		end
135	else
136		assert(io.stderr:write("Temp files left in " .. tmpspace ..
137		    "\n"))
138	end
139end
140
141local function abort(status, msg)
142	assert(io.stderr:write(msg .. "\n"))
143	cleanup()
144	os.exit(status)
145end
146
147-- Each entry should have a value so we can represent abi flags as a bitmask
148-- for convenience.  One may also optionally provide an expr; this gets applied
149-- to each argument type to indicate whether this argument is subject to ABI
150-- change given the configured flags.
151local known_abi_flags = {
152	long_size = {
153		value	= 0x00000001,
154		exprs	= {
155			"_Contains[a-z_]*_long_",
156			"^long [a-z0-9_]+$",
157			"long [*]",
158			"size_t [*]",
159			-- semid_t is not included because it is only used
160			-- as an argument or written out individually and
161			-- said writes are handled by the ksem framework.
162			-- Technically a sign-extension issue exists for
163			-- arguments, but because semid_t is actually a file
164			-- descriptor negative 32-bit values are invalid
165			-- regardless of sign-extension.
166		},
167	},
168	time_t_size = {
169		value	= 0x00000002,
170		exprs	= {
171			"_Contains[a-z_]*_timet_",
172		},
173	},
174	pointer_args = {
175		value	= 0x00000004,
176	},
177	pointer_size = {
178		value	= 0x00000008,
179		exprs	= {
180			"_Contains[a-z_]*_ptr_",
181			"[*][*]",
182		},
183	},
184	pair_64bit = {
185		value	= 0x00000010,
186		exprs	= {
187			"^dev_t[ ]*$",
188			"^id_t[ ]*$",
189			"^off_t[ ]*$",
190		},
191	},
192}
193
194local known_flags = {
195	STD		= 0x00000001,
196	OBSOL		= 0x00000002,
197	RESERVED	= 0x00000004,
198	UNIMPL		= 0x00000008,
199	NODEF		= 0x00000010,
200	NOARGS		= 0x00000020,
201	NOPROTO		= 0x00000040,
202	NOSTD		= 0x00000080,
203	NOTSTATIC	= 0x00000100,
204	CAPENABLED	= 0x00000200,
205	SYSMUX		= 0x00000400,
206
207	-- Compat flags start from here.  We have plenty of space.
208}
209
210-- All compat option entries should have five entries:
211--	definition: The preprocessor macro that will be set for this
212--	compatlevel: The level this compatibility should be included at.  This
213--	    generally represents the version of FreeBSD that it is compatible
214--	    with, but ultimately it's just the level of mincompat in which it's
215--	    included.
216--	flag: The name of the flag in syscalls.master.
217--	prefix: The prefix to use for _args and syscall prototype.  This will be
218--	    used as-is, without "_" or any other character appended.
219--	descr: The description of this compat option in init_sysent.c comments.
220-- The special "stdcompat" entry will cause the other five to be autogenerated.
221local compat_option_sets = {
222	native = {
223		{
224			definition = "COMPAT_43",
225			compatlevel = 3,
226			flag = "COMPAT",
227			prefix = "o",
228			descr = "old",
229		},
230		{ stdcompat = "FREEBSD4" },
231		{ stdcompat = "FREEBSD6" },
232		{ stdcompat = "FREEBSD7" },
233		{ stdcompat = "FREEBSD10" },
234		{ stdcompat = "FREEBSD11" },
235		{ stdcompat = "FREEBSD12" },
236		{ stdcompat = "FREEBSD13" },
237		{ stdcompat = "FREEBSD14" },
238	},
239}
240
241-- compat_options will be resolved to a set from the configuration.
242local compat_options
243
244local function trim(s, char)
245	if s == nil then
246		return nil
247	end
248	if char == nil then
249		char = "%s"
250	end
251	return s:gsub("^" .. char .. "+", ""):gsub(char .. "+$", "")
252end
253
254-- config looks like a shell script; in fact, the previous makesyscalls.sh
255-- script actually sourced it in.  It had a pretty common format, so we should
256-- be fine to make various assumptions
257local function process_config(file)
258	local cfg = {}
259	local comment_line_expr = "^%s*#.*"
260	-- We capture any whitespace padding here so we can easily advance to
261	-- the end of the line as needed to check for any trailing bogus bits.
262	-- Alternatively, we could drop the whitespace and instead try to
263	-- use a pattern to strip out the meaty part of the line, but then we
264	-- would need to sanitize the line for potentially special characters.
265	local line_expr = "^([%w%p]+%s*)=(%s*[`\"]?[^\"`]*[`\"]?)"
266
267	if not file then
268		return nil, "No file given"
269	end
270
271	local fh = assert(io.open(file))
272
273	for nextline in fh:lines() do
274		-- Strip any whole-line comments
275		nextline = nextline:gsub(comment_line_expr, "")
276		-- Parse it into key, value pairs
277		local key, value = nextline:match(line_expr)
278		if key ~= nil and value ~= nil then
279			local kvp = key .. "=" .. value
280			key = trim(key)
281			value = trim(value)
282			local delim = value:sub(1,1)
283			if delim == '"' then
284				local trailing_context
285
286				-- Strip off the key/value part
287				trailing_context = nextline:sub(kvp:len() + 1)
288				-- Strip off any trailing comment
289				trailing_context = trailing_context:gsub("#.*$",
290				    "")
291				-- Strip off leading/trailing whitespace
292				trailing_context = trim(trailing_context)
293				if trailing_context ~= "" then
294					print(trailing_context)
295					abort(1, "Malformed line: " .. nextline)
296				end
297
298				value = trim(value, delim)
299			else
300				-- Strip off potential comments
301				value = value:gsub("#.*$", "")
302				-- Strip off any padding whitespace
303				value = trim(value)
304				if value:match("%s") then
305					abort(1, "Malformed config line: " ..
306					    nextline)
307				end
308			end
309			cfg[key] = value
310		elseif not nextline:match("^%s*$") then
311			-- Make sure format violations don't get overlooked
312			-- here, but ignore blank lines.  Comments are already
313			-- stripped above.
314			abort(1, "Malformed config line: " .. nextline)
315		end
316	end
317
318	assert(io.close(fh))
319	return cfg
320end
321
322local function grab_capenabled(file, open_fail_ok)
323	local capentries = {}
324	local commentExpr = "#.*"
325
326	if file == nil then
327		print "No file"
328		return {}
329	end
330
331	local fh = io.open(file)
332	if fh == nil then
333		if not open_fail_ok then
334			abort(1, "Failed to open " .. file)
335		end
336		return {}
337	end
338
339	for nextline in fh:lines() do
340		-- Strip any comments
341		nextline = nextline:gsub(commentExpr, "")
342		if nextline ~= "" then
343			capentries[nextline] = true
344		end
345	end
346
347	assert(io.close(fh))
348	return capentries
349end
350
351local function process_compat()
352	local nval = 0
353	for _, v in pairs(known_flags) do
354		if v > nval then
355			nval = v
356		end
357	end
358
359	nval = nval << 1
360	for _, v in pairs(compat_options) do
361		if v.stdcompat ~= nil then
362			local stdcompat = v.stdcompat
363			v.definition = "COMPAT_" .. stdcompat:upper()
364			v.compatlevel = tonumber(stdcompat:match("([0-9]+)$"))
365			v.flag = stdcompat:gsub("FREEBSD", "COMPAT")
366			v.prefix = stdcompat:lower() .. "_"
367			v.descr = stdcompat:lower()
368		end
369
370		local tmpname = "sys" .. v.flag:lower()
371		local dcltmpname = tmpname .. "dcl"
372		files[tmpname] = io.tmpfile()
373		files[dcltmpname] = io.tmpfile()
374		v.tmp = tmpname
375		v.dcltmp = dcltmpname
376
377		known_flags[v.flag] = nval
378		v.mask = nval
379		nval = nval << 1
380
381		v.count = 0
382	end
383end
384
385local function process_abi_flags()
386	local flags, mask = config.abi_flags, 0
387	for txtflag in flags:gmatch("([^|]+)") do
388		if known_abi_flags[txtflag] == nil then
389			abort(1, "Unknown abi_flag: " .. txtflag)
390		end
391
392		mask = mask | known_abi_flags[txtflag].value
393	end
394
395	config.abi_flags_mask = mask
396end
397
398local function process_obsol()
399	local obsol = config.obsol
400	for syscall in obsol:gmatch("([^ ]+)") do
401		config.obsol_dict[syscall] = true
402	end
403end
404
405local function process_unimpl()
406	local unimpl = config.unimpl
407	for syscall in unimpl:gmatch("([^ ]+)") do
408		config.unimpl_dict[syscall] = true
409	end
410end
411
412local function process_syscall_abi_change()
413	local changes_abi = config.syscall_abi_change
414	for syscall in changes_abi:gmatch("([^ ]+)") do
415		config.sys_abi_change[syscall] = true
416	end
417
418	local no_changes = config.syscall_no_abi_change
419	for syscall in no_changes:gmatch("([^ ]+)") do
420		config.sys_no_abi_change[syscall] = true
421	end
422end
423
424local function abi_changes(name)
425	if known_abi_flags[name] == nil then
426		abort(1, "abi_changes: unknown flag: " .. name)
427	end
428
429	return config.abi_flags_mask & known_abi_flags[name].value ~= 0
430end
431
432local function strip_abi_prefix(funcname)
433	local abiprefix = config.abi_func_prefix
434	local stripped_name
435	if funcname == nil then
436		return nil
437	end
438	if abiprefix ~= "" and funcname:find("^" .. abiprefix) then
439		stripped_name = funcname:gsub("^" .. abiprefix, "")
440	else
441		stripped_name = funcname
442	end
443
444	return stripped_name
445end
446
447local function read_file(tmpfile)
448	if files[tmpfile] == nil then
449		print("Not found: " .. tmpfile)
450		return
451	end
452
453	local fh = files[tmpfile]
454	assert(fh:seek("set"))
455	return assert(fh:read("a"))
456end
457
458local function write_line(tmpfile, line)
459	if files[tmpfile] == nil then
460		print("Not found: " .. tmpfile)
461		return
462	end
463	assert(files[tmpfile]:write(line))
464end
465
466local function write_line_pfile(tmppat, line)
467	for k in pairs(files) do
468		if k:match(tmppat) ~= nil then
469			assert(files[k]:write(line))
470		end
471	end
472end
473
474-- Check both literal intptr_t and the abi version because this needs
475-- to work both before and after the substitution
476local function isptrtype(type)
477	return type:find("*") or type:find("caddr_t") or
478	    type:find("intptr_t") or type:find(config.abi_intptr_t)
479end
480
481local function isptrarraytype(type)
482	return type:find("[*][*]") or type:find("[*][ ]*const[ ]*[*]")
483end
484
485-- Find types that are always 64-bits wide
486local function is64bittype(type)
487	return type:find("^dev_t[ ]*$") or type:find("^id_t[ ]*$") or type:find("^off_t[ ]*$")
488end
489
490local process_syscall_def
491
492-- These patterns are processed in order on any line that isn't empty.
493local pattern_table = {
494	{
495		-- To be removed soon
496		pattern = "%s*$" .. config.os_id_keyword,
497		process = function(_, _)
498			-- Ignore... ID tag
499		end,
500	},
501	{
502		dump_prevline = true,
503		pattern = "^#%s*include",
504		process = function(line)
505			line = line .. "\n"
506			write_line("sysinc", line)
507		end,
508	},
509	{
510		dump_prevline = true,
511		pattern = "^#",
512		process = function(line)
513			if line:find("^#%s*if") then
514				savesyscall = maxsyscall
515			elseif line:find("^#%s*else") then
516				maxsyscall = savesyscall
517			end
518			line = line .. "\n"
519			write_line("sysent", line)
520			write_line("sysdcl", line)
521			write_line("sysarg", line)
522			write_line_pfile("syscompat[0-9]*$", line)
523			write_line("sysnames", line)
524			write_line_pfile("systrace.*", line)
525		end,
526	},
527	{
528		dump_prevline = true,
529		pattern = "%%ABI_HEADERS%%",
530		process = function()
531			if config.abi_headers ~= "" then
532				local line = config.abi_headers .. "\n"
533				write_line("sysinc", line)
534			end
535		end,
536	},
537	{
538		-- Buffer anything else
539		pattern = ".+",
540		process = function(line, prevline)
541			local incomplete = line:find("\\$") ~= nil
542			-- Lines that end in \ get the \ stripped
543			-- Lines that start with a syscall number, prepend \n
544			line = trim(line):gsub("\\$", "")
545			if line:find("^[0-9]") and prevline then
546				process_syscall_def(prevline)
547				prevline = nil
548			end
549
550			prevline = (prevline or '') .. line
551			incomplete = incomplete or prevline:find(",$") ~= nil
552			incomplete = incomplete or prevline:find("{") ~= nil and
553			    prevline:find("}") == nil
554			if prevline:find("^[0-9]") and not incomplete then
555				process_syscall_def(prevline)
556				prevline = nil
557			end
558
559			return prevline
560		end,
561	},
562}
563
564local function process_sysfile(file)
565	local capentries = {}
566	local commentExpr = "^%s*;.*"
567
568	if file == nil then
569		print "No file"
570		return {}
571	end
572
573	local fh = io.open(file)
574	if fh == nil then
575		print("Failed to open " .. file)
576		return {}
577	end
578
579	local function do_match(nextline, prevline)
580		local pattern, handler, dump
581		for _, v in pairs(pattern_table) do
582			pattern = v.pattern
583			handler = v.process
584			dump = v.dump_prevline
585			if nextline:match(pattern) then
586				if dump and prevline then
587					process_syscall_def(prevline)
588					prevline = nil
589				end
590
591				return handler(nextline, prevline)
592			end
593		end
594
595		abort(1, "Failed to handle: " .. nextline)
596	end
597
598	local prevline
599	for nextline in fh:lines() do
600		-- Strip any comments
601		nextline = nextline:gsub(commentExpr, "")
602		if nextline ~= "" then
603			prevline = do_match(nextline, prevline)
604		end
605	end
606
607	-- Dump any remainder
608	if prevline ~= nil and prevline:find("^[0-9]") then
609		process_syscall_def(prevline)
610	end
611
612	assert(io.close(fh))
613	return capentries
614end
615
616local function get_mask(flags)
617	local mask = 0
618	for _, v in ipairs(flags) do
619		if known_flags[v] == nil then
620			abort(1, "Checking for unknown flag " .. v)
621		end
622
623		mask = mask | known_flags[v]
624	end
625
626	return mask
627end
628
629local function get_mask_pat(pflags)
630	local mask = 0
631	for k, v in pairs(known_flags) do
632		if k:find(pflags) then
633			mask = mask | v
634		end
635	end
636
637	return mask
638end
639
640local function align_sysent_comment(col)
641	write_line("sysent", "\t")
642	col = col + 8 - col % 8
643	while col < 56 do
644		write_line("sysent", "\t")
645		col = col + 8
646	end
647end
648
649local function strip_arg_annotations(arg)
650	arg = arg:gsub("_Contains_[^ ]*[_)] ?", "")
651	arg = arg:gsub("_In[^ ]*[_)] ?", "")
652	arg = arg:gsub("_Out[^ ]*[_)] ?", "")
653	return trim(arg)
654end
655
656local function check_abi_changes(arg)
657	for k, v in pairs(known_abi_flags) do
658		local exprs = v.exprs
659		if abi_changes(k) and exprs ~= nil then
660			for _, e in pairs(exprs) do
661				if arg:find(e) then
662					return true
663				end
664			end
665		end
666	end
667
668	return false
669end
670
671local function process_args(args)
672	local funcargs = {}
673	local changes_abi = false
674
675	for arg in args:gmatch("([^,]+)") do
676		local arg_abi_change = check_abi_changes(arg)
677		changes_abi = changes_abi or arg_abi_change
678
679		arg = strip_arg_annotations(arg)
680
681		local argname = arg:match("([^* ]+)$")
682
683		-- argtype is... everything else.
684		local argtype = trim(arg:gsub(argname .. "$", ""), nil)
685
686		if argtype == "" and argname == "void" then
687			goto out
688		end
689
690		-- is64bittype() needs a bare type so check it after argname
691		-- is removed
692		changes_abi = changes_abi or (abi_changes("pair_64bit") and is64bittype(argtype))
693
694		argtype = argtype:gsub("intptr_t", config.abi_intptr_t)
695		argtype = argtype:gsub("semid_t", config.abi_semid_t)
696		if isptrtype(argtype) then
697			argtype = argtype:gsub("size_t", config.abi_size_t)
698			argtype = argtype:gsub("^long", config.abi_long);
699			argtype = argtype:gsub("^u_long", config.abi_u_long);
700			argtype = argtype:gsub("^const u_long", "const " .. config.abi_u_long);
701		elseif argtype:find("^long$") then
702			argtype = config.abi_long
703		end
704		if isptrarraytype(argtype) and config.abi_ptr_array_t ~= "" then
705			-- `* const *` -> `**`
706			argtype = argtype:gsub("[*][ ]*const[ ]*[*]", "**")
707			-- e.g., `struct aiocb **` -> `uint32_t *`
708			argtype = argtype:gsub("[^*]*[*]", config.abi_ptr_array_t .. " ", 1)
709		end
710
711		-- XX TODO: Forward declarations? See: sysstubfwd in CheriBSD
712		if arg_abi_change then
713			local abi_type_suffix = config.abi_type_suffix
714			argtype = argtype:gsub("(struct [^ ]*)", "%1" ..
715			    abi_type_suffix)
716			argtype = argtype:gsub("(union [^ ]*)", "%1" ..
717			    abi_type_suffix)
718		end
719
720		if abi_changes("pair_64bit") and is64bittype(argtype) then
721			if #funcargs % 2 == 1 then
722				funcargs[#funcargs + 1] = {
723					type = "int",
724					name = "_pad",
725				}
726			end
727			funcargs[#funcargs + 1] = {
728				type = "uint32_t",
729				name = argname .. "1",
730			}
731			funcargs[#funcargs + 1] = {
732				type = "uint32_t",
733				name = argname .. "2",
734			}
735		else
736			funcargs[#funcargs + 1] = {
737				type = argtype,
738				name = argname,
739			}
740		end
741	end
742
743	::out::
744	return funcargs, changes_abi
745end
746
747local function handle_noncompat(sysnum, thr_flag, flags, sysflags, rettype,
748    auditev, syscallret, funcname, funcalias, funcargs, argalias)
749	local argssize
750
751	if flags & known_flags.SYSMUX ~= 0 then
752		argssize = "0"
753	elseif #funcargs > 0 or flags & known_flags.NODEF ~= 0 then
754		argssize = "AS(" .. argalias .. ")"
755	else
756		argssize = "0"
757	end
758
759	write_line("systrace", string.format([[
760	/* %s */
761	case %d: {
762]], funcname, sysnum))
763	write_line("systracetmp", string.format([[
764	/* %s */
765	case %d:
766]], funcname, sysnum))
767	write_line("systraceret", string.format([[
768	/* %s */
769	case %d:
770]], funcname, sysnum))
771
772	if #funcargs > 0 and flags & known_flags.SYSMUX == 0 then
773		write_line("systracetmp", "\t\tswitch (ndx) {\n")
774		write_line("systrace", string.format(
775		    "\t\tstruct %s *p = params;\n", argalias))
776
777
778		local argtype, argname, desc, padding
779		padding = ""
780		for idx, arg in ipairs(funcargs) do
781			argtype = arg.type
782			argname = arg.name
783
784			argtype = trim(argtype:gsub("__restrict$", ""), nil)
785			if argtype == "int" and argname == "_pad" and abi_changes("pair_64bit") then
786				write_line("systracetmp", "#ifdef PAD64_REQUIRED\n")
787			end
788			-- Pointer arg?
789			if argtype:find("*") then
790				desc = "userland " .. argtype
791			else
792				desc = argtype;
793			end
794			write_line("systracetmp", string.format(
795			    "\t\tcase %d%s:\n\t\t\tp = \"%s\";\n\t\t\tbreak;\n",
796			    idx - 1, padding, desc))
797			if argtype == "int" and argname == "_pad" and abi_changes("pair_64bit") then
798				padding = " - _P_"
799				write_line("systracetmp", "#define _P_ 0\n#else\n#define _P_ 1\n#endif\n")
800			end
801
802			if isptrtype(argtype) then
803				write_line("systrace", string.format(
804				    "\t\tuarg[a++] = (%s)p->%s; /* %s */\n",
805				    config.ptr_intptr_t_cast,
806				    argname, argtype))
807			elseif argtype == "union l_semun" then
808				write_line("systrace", string.format(
809				    "\t\tuarg[a++] = p->%s.buf; /* %s */\n",
810				    argname, argtype))
811			elseif argtype:sub(1,1) == "u" or argtype == "size_t" then
812				write_line("systrace", string.format(
813				    "\t\tuarg[a++] = p->%s; /* %s */\n",
814				    argname, argtype))
815			else
816				if argtype == "int" and argname == "_pad" and abi_changes("pair_64bit") then
817					write_line("systrace", "#ifdef PAD64_REQUIRED\n")
818				end
819				write_line("systrace", string.format(
820				    "\t\tiarg[a++] = p->%s; /* %s */\n",
821				    argname, argtype))
822				if argtype == "int" and argname == "_pad" and abi_changes("pair_64bit") then
823					write_line("systrace", "#endif\n")
824				end
825			end
826		end
827
828		write_line("systracetmp",
829		    "\t\tdefault:\n\t\t\tbreak;\n\t\t};\n")
830		if padding ~= "" then
831			write_line("systracetmp", "#undef _P_\n\n")
832		end
833
834		write_line("systraceret", string.format([[
835		if (ndx == 0 || ndx == 1)
836			p = "%s";
837		break;
838]], syscallret))
839	end
840	local n_args = #funcargs
841	if flags & known_flags.SYSMUX ~= 0 then
842		n_args = 0
843	end
844	write_line("systrace", string.format(
845	    "\t\t*n_args = %d;\n\t\tbreak;\n\t}\n", n_args))
846	write_line("systracetmp", "\t\tbreak;\n")
847
848	local nargflags = get_mask({"NOARGS", "NOPROTO", "NODEF"})
849	if flags & nargflags == 0 then
850		if #funcargs > 0 then
851			write_line("sysarg", string.format("struct %s {\n",
852			    argalias))
853			for _, v in ipairs(funcargs) do
854				local argname, argtype = v.name, v.type
855				if argtype == "int" and argname == "_pad" and abi_changes("pair_64bit") then
856					write_line("sysarg", "#ifdef PAD64_REQUIRED\n")
857				end
858				write_line("sysarg", string.format(
859				    "\tchar %s_l_[PADL_(%s)]; %s %s; char %s_r_[PADR_(%s)];\n",
860				    argname, argtype,
861				    argtype, argname,
862				    argname, argtype))
863				if argtype == "int" and argname == "_pad" and abi_changes("pair_64bit") then
864					write_line("sysarg", "#endif\n")
865				end
866			end
867			write_line("sysarg", "};\n")
868		else
869			write_line("sysarg", string.format(
870			    "struct %s {\n\tsyscallarg_t dummy;\n};\n", argalias))
871		end
872	end
873
874	local protoflags = get_mask({"NOPROTO", "NODEF"})
875	if flags & protoflags == 0 then
876		local sys_prefix = "sys_"
877		if funcname == "nosys" or funcname == "lkmnosys" or
878		    funcname == "sysarch" or funcname:find("^freebsd") or
879		    funcname:find("^linux") then
880			sys_prefix = ""
881		end
882		write_line("sysdcl", string.format(
883		    "%s\t%s%s(struct thread *, struct %s *);\n",
884		    rettype, sys_prefix, funcname, argalias))
885		write_line("sysaue", string.format("#define\t%sAUE_%s\t%s\n",
886		    config.syscallprefix, funcalias, auditev))
887	end
888
889	write_line("sysent",
890	    string.format("\t{ .sy_narg = %s, .sy_call = (sy_call_t *)", argssize))
891	local column = 8 + 2 + #argssize + 15
892
893	if flags & known_flags.SYSMUX ~= 0 then
894		write_line("sysent", string.format(
895		    "nosys, .sy_auevent = AUE_NULL, " ..
896		    ".sy_flags = %s, .sy_thrcnt = SY_THR_STATIC },",
897		    sysflags))
898		column = column + #"nosys" + #"AUE_NULL" + 3
899	elseif flags & known_flags.NOSTD ~= 0 then
900		write_line("sysent", string.format(
901		    "lkmressys, .sy_auevent = AUE_NULL, " ..
902		    ".sy_flags = %s, .sy_thrcnt = SY_THR_ABSENT },",
903		    sysflags))
904		column = column + #"lkmressys" + #"AUE_NULL" + 3
905	else
906		if funcname == "nosys" or funcname == "lkmnosys" or
907		    funcname == "sysarch" or funcname:find("^freebsd") or
908		    funcname:find("^linux") then
909			write_line("sysent", string.format(
910			    "%s, .sy_auevent = %s, .sy_flags = %s, .sy_thrcnt = %s },",
911			    funcname, auditev, sysflags, thr_flag))
912			column = column + #funcname + #auditev + #sysflags + 3
913		else
914			write_line("sysent", string.format(
915			    "sys_%s, .sy_auevent = %s, .sy_flags = %s, .sy_thrcnt = %s },",
916			    funcname, auditev, sysflags, thr_flag))
917			column = column + #funcname + #auditev + #sysflags + 7
918		end
919	end
920
921	align_sysent_comment(column)
922	write_line("sysent", string.format("/* %d = %s */\n",
923	    sysnum, funcalias))
924	write_line("sysnames", string.format("\t\"%s\",\t\t\t/* %d = %s */\n",
925	    funcalias, sysnum, funcalias))
926
927	if flags & known_flags.NODEF == 0 then
928		write_line("syshdr", string.format("#define\t%s%s\t%d\n",
929		    config.syscallprefix, funcalias, sysnum))
930		write_line("sysmk", string.format(" \\\n\t%s.o",
931		    funcalias))
932		-- yield has never been exposed as a syscall
933		if funcalias == "yield" then
934			return
935		end
936		if funcalias ~= "exit" and funcalias ~= "vfork" then
937			write_line("libsysmap", string.format("\t_%s;\n",
938			    funcalias))
939		end
940		write_line("libsysmap", string.format("\t__sys_%s;\n",
941		    funcalias))
942
943		if flags & known_flags.SYSMUX == 0 then
944			local argstr_type = ""
945			local argstr_var = ""
946			local comma = ""
947			if #funcargs == 0 then
948				argstr_type = "void"
949				argstr_var = "void"
950			end
951			for _, v in ipairs(funcargs) do
952				local argname, argtype = v.name, v.type
953				argstr_type = argstr_type .. comma .. argtype
954				argstr_var = argstr_var .. comma .. argtype .. " " .. argname
955				comma = ", "
956
957				-- Accumulate a list of struct types for
958				-- forward decls.  We can't do this in
959				-- process_args because we don't want compat
960				-- types in userspace even as no-op.
961				if isptrtype(argtype) then
962					local is_struct = false
963					for word in argtype:gmatch("[^ *]+") do
964						if is_struct then
965							structs[word] = word
966							break
967						end
968						if word == "struct" then
969							is_struct = true
970							-- next word is the name
971						end
972					end
973				end
974			end
975			write_line("libsys_h_type",
976			    string.format("typedef %s (__sys_%s_t)(%s);\n",
977			    syscallret, funcalias, argstr_type))
978			write_line("libsys_h_func",
979			    string.format("%s __sys_%s(%s);\n",
980			    syscallret, funcalias, argstr_var))
981
982		end
983	end
984end
985
986local function handle_obsol(sysnum, funcname, comment)
987	write_line("sysent",
988	    "\t{ .sy_narg = 0, .sy_call = (sy_call_t *)nosys, " ..
989	    ".sy_auevent = AUE_NULL, .sy_flags = 0, .sy_thrcnt = SY_THR_ABSENT },")
990	align_sysent_comment(34)
991
992	write_line("sysent", string.format("/* %d = obsolete %s */\n",
993	    sysnum, comment))
994	write_line("sysnames", string.format(
995	    "\t\"obs_%s\",\t\t\t/* %d = obsolete %s */\n",
996	    funcname, sysnum, comment))
997	write_line("syshdr", string.format("\t\t\t\t/* %d is obsolete %s */\n",
998	    sysnum, comment))
999end
1000
1001local function handle_compat(sysnum, thr_flag, flags, sysflags, rettype,
1002    auditev, funcname, funcalias, funcargs, argalias)
1003	local argssize, out, outdcl, wrap, prefix, descr
1004
1005	if #funcargs > 0 or flags & known_flags.NODEF ~= 0 then
1006		argssize = "AS(" .. argalias .. ")"
1007	else
1008		argssize = "0"
1009	end
1010
1011	for _, v in pairs(compat_options) do
1012		if flags & v.mask ~= 0 then
1013			if config.mincompat > v.compatlevel then
1014				funcname = strip_abi_prefix(funcname)
1015				funcname = v.prefix .. funcname
1016				return handle_obsol(sysnum, funcname, funcname)
1017			end
1018			v.count = v.count + 1
1019			out = v.tmp
1020			outdcl = v.dcltmp
1021			wrap = v.flag:lower()
1022			prefix = v.prefix
1023			descr = v.descr
1024			goto compatdone
1025		end
1026	end
1027
1028	::compatdone::
1029	local dprotoflags = get_mask({"NOPROTO", "NODEF"})
1030	local nargflags = dprotoflags | known_flags.NOARGS
1031	if #funcargs > 0 and flags & nargflags == 0 then
1032		write_line(out, string.format("struct %s {\n", argalias))
1033		for _, v in ipairs(funcargs) do
1034			local argname, argtype = v.name, v.type
1035			write_line(out, string.format(
1036			    "\tchar %s_l_[PADL_(%s)]; %s %s; char %s_r_[PADR_(%s)];\n",
1037			    argname, argtype,
1038			    argtype, argname,
1039			    argname, argtype))
1040		end
1041		write_line(out, "};\n")
1042	elseif flags & nargflags == 0 then
1043		write_line("sysarg", string.format(
1044		    "struct %s {\n\tsyscallarg_t dummy;\n};\n", argalias))
1045	end
1046	if flags & dprotoflags == 0 then
1047		write_line(outdcl, string.format(
1048		    "%s\t%s%s(struct thread *, struct %s *);\n",
1049		    rettype, prefix, funcname, argalias))
1050		write_line("sysaue", string.format(
1051		    "#define\t%sAUE_%s%s\t%s\n", config.syscallprefix,
1052		    prefix, funcname, auditev))
1053	end
1054
1055	if flags & known_flags.NOSTD ~= 0 then
1056		write_line("sysent", string.format(
1057		    "\t{ .sy_narg = %s, .sy_call = (sy_call_t *)%s, " ..
1058		    ".sy_auevent = %s, .sy_flags = 0, " ..
1059		    ".sy_thrcnt = SY_THR_ABSENT },",
1060		    "0", "lkmressys", "AUE_NULL"))
1061		align_sysent_comment(8 + 2 + #"0" + 15 + #"lkmressys" +
1062		    #"AUE_NULL" + 3)
1063	else
1064		write_line("sysent", string.format(
1065		    "\t{ %s(%s,%s), .sy_auevent = %s, .sy_flags = %s, .sy_thrcnt = %s },",
1066		    wrap, argssize, funcname, auditev, sysflags, thr_flag))
1067		align_sysent_comment(8 + 9 + #argssize + 1 + #funcname +
1068		    #auditev + #sysflags + 4)
1069	end
1070
1071	write_line("sysent", string.format("/* %d = %s %s */\n",
1072	    sysnum, descr, funcalias))
1073	write_line("sysnames", string.format(
1074	    "\t\"%s.%s\",\t\t/* %d = %s %s */\n",
1075	    wrap, funcalias, sysnum, descr, funcalias))
1076	-- Do not provide freebsdN_* symbols in libc for < FreeBSD 7
1077	local nosymflags = get_mask({"COMPAT", "COMPAT4", "COMPAT6"})
1078	if flags & nosymflags ~= 0 then
1079		write_line("syshdr", string.format(
1080		    "\t\t\t\t/* %d is %s %s */\n",
1081		    sysnum, descr, funcalias))
1082	elseif flags & known_flags.NODEF == 0 then
1083		write_line("syshdr", string.format("#define\t%s%s%s\t%d\n",
1084		    config.syscallprefix, prefix, funcalias, sysnum))
1085		write_line("sysmk", string.format(" \\\n\t%s%s.o",
1086		    prefix, funcalias))
1087	end
1088end
1089
1090local function handle_unimpl(sysnum, sysstart, sysend, comment)
1091	if sysstart == nil and sysend == nil then
1092		sysstart = tonumber(sysnum)
1093		sysend = tonumber(sysnum)
1094	end
1095
1096	sysnum = sysstart
1097	while sysnum <= sysend do
1098		write_line("sysent", string.format(
1099		    "\t{ .sy_narg = 0, .sy_call = (sy_call_t *)nosys, " ..
1100		    ".sy_auevent = AUE_NULL, .sy_flags = 0, " ..
1101		    ".sy_thrcnt = SY_THR_ABSENT },\t\t\t/* %d = %s */\n",
1102		    sysnum, comment))
1103		write_line("sysnames", string.format(
1104		    "\t\"#%d\",\t\t\t/* %d = %s */\n",
1105		    sysnum, sysnum, comment))
1106		sysnum = sysnum + 1
1107	end
1108end
1109
1110local function handle_reserved(sysnum, sysstart, sysend)
1111	handle_unimpl(sysnum, sysstart, sysend, "reserved for local use")
1112end
1113
1114process_syscall_def = function(line)
1115	local sysstart, sysend, flags, funcname, sysflags
1116	local thr_flag, syscallret
1117	local orig = line
1118	flags = 0
1119	thr_flag = "SY_THR_STATIC"
1120
1121	-- Parse out the interesting information first
1122	local initialExpr = "^([^%s]+)%s+([^%s]+)%s+([^%s]+)%s*"
1123	local sysnum, auditev, allflags = line:match(initialExpr)
1124
1125	if sysnum == nil or auditev == nil or allflags == nil then
1126		-- XXX TODO: Better?
1127		abort(1, "Completely malformed: " .. line)
1128	end
1129
1130	if sysnum:find("-") then
1131		sysstart, sysend = sysnum:match("^([%d]+)-([%d]+)$")
1132		if sysstart == nil or sysend == nil then
1133			abort(1, "Malformed range: " .. sysnum)
1134		end
1135		sysnum = nil
1136		sysstart = tonumber(sysstart)
1137		sysend = tonumber(sysend)
1138		if sysstart ~= maxsyscall + 1 then
1139			abort(1, "syscall number out of sync, missing " ..
1140			    maxsyscall + 1)
1141		end
1142	else
1143		sysnum = tonumber(sysnum)
1144		if sysnum ~= maxsyscall + 1 then
1145			abort(1, "syscall number out of sync, missing " ..
1146			    maxsyscall + 1)
1147		end
1148	end
1149
1150	-- Split flags
1151	for flag in allflags:gmatch("([^|]+)") do
1152		if known_flags[flag] == nil then
1153			abort(1, "Unknown flag " .. flag .. " for " ..  sysnum)
1154		end
1155		flags = flags | known_flags[flag]
1156	end
1157
1158	if (flags & get_mask({"RESERVED", "UNIMPL"})) == 0 and sysnum == nil then
1159		abort(1, "Range only allowed with RESERVED and UNIMPL: " .. line)
1160	end
1161
1162	if (flags & known_flags.NOTSTATIC) ~= 0 then
1163		thr_flag = "SY_THR_ABSENT"
1164	end
1165
1166	-- Strip earlier bits out, leave declaration + alt
1167	line = line:gsub("^.+" .. allflags .. "%s*", "")
1168
1169	local decl_fnd = line:find("^{") ~= nil
1170	if decl_fnd and line:find("}") == nil then
1171		abort(1, "Malformed, no closing brace: " .. line)
1172	end
1173
1174	local decl, alt
1175	if decl_fnd then
1176		line = line:gsub("^{", "")
1177		decl, alt = line:match("([^}]*)}[%s]*(.*)$")
1178	else
1179		alt = line
1180	end
1181
1182	if decl == nil and alt == nil then
1183		abort(1, "Malformed bits: " .. line)
1184	end
1185
1186	local funcalias, funcomment, argalias, rettype, args
1187	if not decl_fnd and alt ~= nil and alt ~= "" then
1188		-- Peel off one entry for name
1189		funcname = trim(alt:match("^([^%s]+)"), nil)
1190		alt = alt:gsub("^([^%s]+)[%s]*", "")
1191	end
1192	-- Do we even need it?
1193	if flags & get_mask({"OBSOL", "UNIMPL"}) ~= 0 then
1194		local NF = 0
1195		for _ in orig:gmatch("[^%s]+") do
1196			NF = NF + 1
1197		end
1198
1199		funcomment = funcname or ''
1200		if NF < 6 then
1201			funcomment = funcomment .. " " .. alt
1202		end
1203
1204		funcomment = trim(funcomment)
1205
1206--		if funcname ~= nil then
1207--		else
1208--			funcomment = trim(alt)
1209--		end
1210		goto skipalt
1211	end
1212
1213	if alt ~= nil and alt ~= "" then
1214		local altExpr = "^([^%s]+)%s+([^%s]+)%s+([^%s]+)"
1215		funcalias, argalias, rettype = alt:match(altExpr)
1216		funcalias = trim(funcalias)
1217		if funcalias == nil or argalias == nil or rettype == nil then
1218			abort(1, "Malformed alt: " .. line)
1219		end
1220	end
1221	if decl_fnd then
1222		-- Don't clobber rettype set in the alt information
1223		if rettype == nil then
1224			rettype = "int"
1225		end
1226		-- Peel off the return type
1227		syscallret = line:match("([^%s]+)%s")
1228		line = line:match("[^%s]+%s(.+)")
1229		-- Pointer incoming
1230		if line:sub(1,1) == "*" then
1231			syscallret = syscallret .. " "
1232		end
1233		while line:sub(1,1) == "*" do
1234			line = line:sub(2)
1235			syscallret = syscallret .. "*"
1236		end
1237		funcname = line:match("^([^(]+)%(")
1238		if funcname == nil then
1239			abort(1, "Not a signature? " .. line)
1240		end
1241		args = line:match("^[^(]+%((.+)%)[^)]*$")
1242		args = trim(args, '[,%s]')
1243	end
1244
1245	::skipalt::
1246
1247	if funcname == nil then
1248		funcname = funcalias
1249	end
1250
1251	funcname = trim(funcname)
1252
1253	if config.obsol_dict[funcname] then
1254		local compat_prefix = ""
1255		for _, v in pairs(compat_options) do
1256			if flags & v.mask ~= 0 then
1257				compat_prefix = v.prefix
1258				goto obsol_compat_done
1259			end
1260		end
1261		::obsol_compat_done::
1262		args = nil
1263		flags = known_flags.OBSOL
1264		funcomment = compat_prefix .. funcname
1265	end
1266	if config.unimpl_dict[funcname] then
1267		flags = known_flags.UNIMPL
1268		funcomment = funcname
1269	end
1270
1271	sysflags = "0"
1272
1273	-- NODEF events do not get audited
1274	if flags & known_flags.NODEF ~= 0 then
1275		auditev = 'AUE_NULL'
1276	end
1277
1278	-- If applicable; strip the ABI prefix from the name
1279	local stripped_name = strip_abi_prefix(funcname)
1280
1281	if flags & known_flags.CAPENABLED ~= 0 or
1282	    config.capenabled[funcname] ~= nil or
1283	    config.capenabled[stripped_name] ~= nil then
1284		sysflags = "SYF_CAPENABLED"
1285	end
1286
1287	local funcargs = {}
1288	local changes_abi = false
1289	if args ~= nil then
1290		funcargs, changes_abi = process_args(args)
1291	end
1292	if config.sys_no_abi_change[funcname] then
1293		changes_abi = false
1294	end
1295	local noproto = config.abi_flags ~= "" and not changes_abi
1296
1297	local argprefix = ''
1298	local funcprefix = ''
1299	if abi_changes("pointer_args") then
1300		for _, v in ipairs(funcargs) do
1301			if isptrtype(v.type) then
1302				if config.sys_no_abi_change[funcname] then
1303					print("WARNING: " .. funcname ..
1304					    " in syscall_no_abi_change, but pointers args are present")
1305				end
1306				changes_abi = true
1307				goto ptrfound
1308			end
1309		end
1310		::ptrfound::
1311	end
1312	if config.sys_abi_change[funcname] then
1313		changes_abi = true
1314	end
1315	if changes_abi then
1316		-- argalias should be:
1317		--   COMPAT_PREFIX + ABI Prefix + funcname
1318		argprefix = config.abi_func_prefix
1319		funcprefix = config.abi_func_prefix
1320		funcalias = funcprefix .. funcname
1321		noproto = false
1322	end
1323	if funcname ~= nil then
1324		funcname = funcprefix .. funcname
1325	end
1326	if funcalias == nil or funcalias == "" then
1327		funcalias = funcname
1328	end
1329
1330	if argalias == nil and funcname ~= nil then
1331		argalias = funcname .. "_args"
1332		for _, v in pairs(compat_options) do
1333			local mask = v.mask
1334			if (flags & mask) ~= 0 then
1335				-- Multiple aliases doesn't seem to make
1336				-- sense.
1337				argalias = v.prefix .. argalias
1338				goto out
1339			end
1340		end
1341		::out::
1342	elseif argalias ~= nil then
1343		argalias = argprefix .. argalias
1344	end
1345
1346	local ncompatflags = get_mask({"STD", "NODEF", "NOARGS", "NOPROTO",
1347	    "NOSTD"})
1348	local compatflags = get_mask_pat("COMPAT.*")
1349	if noproto or flags & known_flags.SYSMUX ~= 0 then
1350		flags = flags | known_flags.NOPROTO;
1351	end
1352	if flags & known_flags.OBSOL ~= 0 then
1353		handle_obsol(sysnum, funcname, funcomment)
1354	elseif flags & known_flags.RESERVED ~= 0 then
1355		handle_reserved(sysnum, sysstart, sysend)
1356	elseif flags & known_flags.UNIMPL ~= 0 then
1357		handle_unimpl(sysnum, sysstart, sysend, funcomment)
1358	elseif flags & compatflags ~= 0 then
1359		if flags & known_flags.STD ~= 0 then
1360			abort(1, "Incompatible COMPAT/STD: " .. line)
1361		end
1362		handle_compat(sysnum, thr_flag, flags, sysflags, rettype,
1363		    auditev, funcname, funcalias, funcargs, argalias)
1364	elseif flags & ncompatflags ~= 0 then
1365		handle_noncompat(sysnum, thr_flag, flags, sysflags, rettype,
1366		    auditev, syscallret, funcname, funcalias, funcargs,
1367		    argalias)
1368	else
1369		abort(1, "Bad flags? " .. line)
1370	end
1371
1372	if sysend ~= nil then
1373		maxsyscall = sysend
1374	elseif sysnum ~= nil then
1375		maxsyscall = sysnum
1376	end
1377end
1378
1379local function pairsByKeys (t, f)
1380	local a = {}
1381	for n in pairs(t) do table.insert(a, n) end
1382	table.sort(a, f)
1383	local i = 0      -- iterator variable
1384	local iter = function ()   -- iterator function
1385		i = i + 1
1386		if a[i] == nil then return nil
1387		else return a[i], t[a[i]]
1388		end
1389	end
1390	return iter
1391end
1392
1393-- Entry point
1394
1395if #arg < 1 or #arg > 2 then
1396	error("usage: " .. arg[0] .. " input-file <config-file>")
1397end
1398
1399local sysfile, configfile = arg[1], arg[2]
1400
1401-- process_config either returns nil and a message, or a
1402-- table that we should merge into the global config
1403if configfile ~= nil then
1404	local res = assert(process_config(configfile))
1405
1406	for k, v in pairs(res) do
1407		if v ~= config[k] then
1408			config[k] = v
1409			config_modified[k] = true
1410		end
1411	end
1412end
1413
1414local compat_set = config.compat_set
1415if compat_set ~= "" then
1416	if not compat_option_sets[compat_set] then
1417		abort(1, "Undefined compat set: " .. compat_set)
1418	end
1419
1420	compat_options = compat_option_sets[compat_set]
1421else
1422	compat_options = {}
1423end
1424
1425-- We ignore errors here if we're relying on the default configuration.
1426if not config_modified.capenabled then
1427	config.capenabled = grab_capenabled(config.capabilities_conf,
1428	    config_modified.capabilities_conf == nil)
1429elseif config.capenabled ~= "" then
1430	-- Due to limitations in the config format mostly, we'll have a comma
1431	-- separated list.  Parse it into lines
1432	local capenabled = {}
1433	-- print("here: " .. config.capenabled)
1434	for sysc in config.capenabled:gmatch("([^,]+)") do
1435		capenabled[sysc] = true
1436	end
1437	config.capenabled = capenabled
1438end
1439process_compat()
1440process_abi_flags()
1441process_syscall_abi_change()
1442process_obsol()
1443process_unimpl()
1444
1445if not lfs.mkdir(tmpspace) then
1446	error("Failed to create tempdir " .. tmpspace)
1447end
1448
1449-- XXX Revisit the error handling here, we should probably move the rest of this
1450-- into a function that we pcall() so we can catch the errors and clean up
1451-- gracefully.
1452for _, v in ipairs(temp_files) do
1453	local tmpname = tmpspace .. v
1454	files[v] = io.open(tmpname, "w+")
1455	-- XXX Revisit these with a pcall() + error handler
1456	if not files[v] then
1457		abort(1, "Failed to open temp file: " .. tmpname)
1458	end
1459end
1460
1461for _, v in ipairs(output_files) do
1462	local tmpname = tmpspace .. v
1463	files[v] = io.open(tmpname, "w+")
1464	-- XXX Revisit these with a pcall() + error handler
1465	if not files[v] then
1466		abort(1, "Failed to open temp output file: " .. tmpname)
1467	end
1468end
1469
1470-- Write out all of the preamble bits
1471write_line("sysent", string.format([[
1472
1473/* The casts are bogus but will do for now. */
1474struct sysent %s[] = {
1475]], config.switchname))
1476
1477write_line("syssw", string.format([[/*
1478 * System call switch table.
1479 *
1480 * DO NOT EDIT-- this file is automatically %s.
1481 */
1482
1483]], generated_tag))
1484
1485write_line("sysarg", string.format([[/*
1486 * System call prototypes.
1487 *
1488 * DO NOT EDIT-- this file is automatically %s.
1489 */
1490
1491#ifndef %s
1492#define	%s
1493
1494#include <sys/types.h>
1495#include <sys/signal.h>
1496#include <sys/cpuset.h>
1497#include <sys/domainset.h>
1498#include <sys/_ffcounter.h>
1499#include <sys/_semaphore.h>
1500#include <sys/ucontext.h>
1501#include <sys/wait.h>
1502
1503#include <bsm/audit_kevents.h>
1504
1505struct proc;
1506
1507struct thread;
1508
1509#define	PAD_(t)	(sizeof(syscallarg_t) <= sizeof(t) ? \
1510		0 : sizeof(syscallarg_t) - sizeof(t))
1511
1512#if BYTE_ORDER == LITTLE_ENDIAN
1513#define	PADL_(t)	0
1514#define	PADR_(t)	PAD_(t)
1515#else
1516#define	PADL_(t)	PAD_(t)
1517#define	PADR_(t)	0
1518#endif
1519
1520]], generated_tag, config.sysproto_h, config.sysproto_h))
1521if abi_changes("pair_64bit") then
1522	write_line("sysarg", string.format([[
1523#if !defined(PAD64_REQUIRED) && !defined(__amd64__)
1524#define PAD64_REQUIRED
1525#endif
1526]]))
1527end
1528if abi_changes("pair_64bit") then
1529	write_line("systrace", string.format([[
1530#if !defined(PAD64_REQUIRED) && !defined(__amd64__)
1531#define PAD64_REQUIRED
1532#endif
1533]]))
1534end
1535for _, v in pairs(compat_options) do
1536	write_line(v.tmp, string.format("\n#ifdef %s\n\n", v.definition))
1537end
1538
1539write_line("sysnames", string.format([[/*
1540 * System call names.
1541 *
1542 * DO NOT EDIT-- this file is automatically %s.
1543 */
1544
1545const char *%s[] = {
1546]], generated_tag, config.namesname))
1547
1548write_line("syshdr", string.format([[/*
1549 * System call numbers.
1550 *
1551 * DO NOT EDIT-- this file is automatically %s.
1552 */
1553
1554]], generated_tag))
1555
1556write_line("sysmk", string.format([[# FreeBSD system call object files.
1557# DO NOT EDIT-- this file is automatically %s.
1558MIASM = ]], generated_tag))
1559
1560write_line("libsysmap", string.format([[/*
1561 * FreeBSD system call symbols.
1562 *  DO NOT EDIT-- this file is automatically %s.
1563 */
1564FBSDprivate_1.0 {
1565]], generated_tag))
1566
1567write_line("libsys_h", string.format([[/*
1568 * Public system call stubs provided by libsys.
1569 *
1570 * Do not use directly, include <libsys.h> instead.
1571 *
1572 *  DO NOT EDIT-- this file is automatically %s.
1573 */
1574#ifndef __LIBSYS_H_
1575#define __LIBSYS_H_
1576
1577#include <sys/_cpuset.h>
1578#include <sys/_domainset.h>
1579#include <sys/_ffcounter.h>
1580#include <sys/_semaphore.h>
1581#include <sys/_sigaltstack.h>
1582#include <machine/ucontext.h>   /* for mcontext_t */
1583#include <sys/_ucontext.h>
1584#include <sys/wait.h>
1585
1586]], generated_tag))
1587
1588write_line("systrace", string.format([[/*
1589 * System call argument to DTrace register array converstion.
1590 *
1591 * DO NOT EDIT-- this file is automatically %s.
1592 * This file is part of the DTrace syscall provider.
1593 */
1594
1595static void
1596systrace_args(int sysnum, void *params, uint64_t *uarg, int *n_args)
1597{
1598	int64_t *iarg = (int64_t *)uarg;
1599	int a = 0;
1600	switch (sysnum) {
1601]], generated_tag))
1602
1603write_line("systracetmp", [[static void
1604systrace_entry_setargdesc(int sysnum, int ndx, char *desc, size_t descsz)
1605{
1606	const char *p = NULL;
1607	switch (sysnum) {
1608]])
1609
1610write_line("systraceret", [[static void
1611systrace_return_setargdesc(int sysnum, int ndx, char *desc, size_t descsz)
1612{
1613	const char *p = NULL;
1614	switch (sysnum) {
1615]])
1616
1617-- Processing the sysfile will parse out the preprocessor bits and put them into
1618-- the appropriate place.  Any syscall-looking lines get thrown into the sysfile
1619-- buffer, one per line, for later processing once they're all glued together.
1620process_sysfile(sysfile)
1621
1622write_line("sysinc",
1623    "\n#define AS(name) (sizeof(struct name) / sizeof(syscallarg_t))\n")
1624
1625for _, v in pairs(compat_options) do
1626	if v.count > 0 then
1627		write_line("sysinc", string.format([[
1628
1629#ifdef %s
1630#define %s(n, name) .sy_narg = n, .sy_call = (sy_call_t *)__CONCAT(%s, name)
1631#else
1632#define %s(n, name) .sy_narg = 0, .sy_call = (sy_call_t *)nosys
1633#endif
1634]], v.definition, v.flag:lower(), v.prefix, v.flag:lower()))
1635	end
1636
1637	write_line(v.dcltmp, string.format("\n#endif /* %s */\n\n",
1638	    v.definition))
1639end
1640
1641write_line("sysprotoend", string.format([[
1642
1643#undef PAD_
1644#undef PADL_
1645#undef PADR_
1646
1647#endif /* !%s */
1648]], config.sysproto_h))
1649
1650write_line("sysmk", "\n")
1651write_line("libsysmap", "};\n")
1652write_line("sysent", "};\n")
1653write_line("sysnames", "};\n")
1654-- maxsyscall is the highest seen; MAXSYSCALL should be one higher
1655write_line("syshdr", string.format("#define\t%sMAXSYSCALL\t%d\n",
1656    config.syscallprefix, maxsyscall + 1))
1657write_line("systrace", [[
1658	default:
1659		*n_args = 0;
1660		break;
1661	};
1662}
1663]])
1664
1665write_line("systracetmp", [[
1666	default:
1667		break;
1668	};
1669	if (p != NULL)
1670		strlcpy(desc, p, descsz);
1671}
1672]])
1673
1674write_line("systraceret", [[
1675	default:
1676		break;
1677	};
1678	if (p != NULL)
1679		strlcpy(desc, p, descsz);
1680}
1681]])
1682
1683-- Finish up; output
1684table.sort(structs)
1685for name,_ in pairsByKeys(structs) do
1686	write_line("libsys_h", string.format("struct %s;\n", name))
1687end
1688write_line("libsys_h", "union semun;\n\n__BEGIN_DECLS\n")
1689write_line("libsys_h", read_file("libsys_h_type"))
1690write_line("libsys_h", "\n")
1691write_line("libsys_h", read_file("libsys_h_func"))
1692write_line("libsys_h", "__END_DECLS\n\n#endif /* __LIBSYS_H_ */\n")
1693
1694write_line("syssw", read_file("sysinc"))
1695write_line("syssw", read_file("sysent"))
1696
1697write_line("sysproto", read_file("sysarg"))
1698write_line("sysproto", read_file("sysdcl"))
1699for _, v in pairs(compat_options) do
1700	write_line("sysproto", read_file(v.tmp))
1701	write_line("sysproto", read_file(v.dcltmp))
1702end
1703write_line("sysproto", read_file("sysaue"))
1704write_line("sysproto", read_file("sysprotoend"))
1705
1706write_line("systrace", read_file("systracetmp"))
1707write_line("systrace", read_file("systraceret"))
1708
1709for _, v in ipairs(output_files) do
1710	local target = config[v]
1711	if target ~= "/dev/null" then
1712		local fh = assert(io.open(target, "w+"))
1713		if fh == nil then
1714			abort(1, "Failed to open '" .. target .. "'")
1715		end
1716		assert(fh:write(read_file(v)))
1717		assert(fh:close())
1718	end
1719end
1720
1721cleanup()
1722