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