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