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