xref: /freebsd/sys/tools/makesyscalls.lua (revision 4d846d26)
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",
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		pattern = "%s*$" .. config.os_id_keyword,
490		process = function(_, _)
491			-- Ignore... ID tag
492		end,
493	},
494	{
495		dump_prevline = true,
496		pattern = "^#%s*include",
497		process = function(line)
498			line = line .. "\n"
499			write_line("sysinc", line)
500		end,
501	},
502	{
503		dump_prevline = true,
504		pattern = "^#",
505		process = function(line)
506			if line:find("^#%s*if") then
507				savesyscall = maxsyscall
508			elseif line:find("^#%s*else") then
509				maxsyscall = savesyscall
510			end
511			line = line .. "\n"
512			write_line("sysent", line)
513			write_line("sysdcl", line)
514			write_line("sysarg", line)
515			write_line_pfile("syscompat[0-9]*$", line)
516			write_line("sysnames", line)
517			write_line_pfile("systrace.*", line)
518		end,
519	},
520	{
521		dump_prevline = true,
522		pattern = "%%ABI_HEADERS%%",
523		process = function()
524			if config.abi_headers ~= "" then
525				local line = config.abi_headers .. "\n"
526				write_line("sysinc", line)
527			end
528		end,
529	},
530	{
531		-- Buffer anything else
532		pattern = ".+",
533		process = function(line, prevline)
534			local incomplete = line:find("\\$") ~= nil
535			-- Lines that end in \ get the \ stripped
536			-- Lines that start with a syscall number, prepend \n
537			line = trim(line):gsub("\\$", "")
538			if line:find("^[0-9]") and prevline then
539				process_syscall_def(prevline)
540				prevline = nil
541			end
542
543			prevline = (prevline or '') .. line
544			incomplete = incomplete or prevline:find(",$") ~= nil
545			incomplete = incomplete or prevline:find("{") ~= nil and
546			    prevline:find("}") == nil
547			if prevline:find("^[0-9]") and not incomplete then
548				process_syscall_def(prevline)
549				prevline = nil
550			end
551
552			return prevline
553		end,
554	},
555}
556
557local function process_sysfile(file)
558	local capentries = {}
559	local commentExpr = "^%s*;.*"
560
561	if file == nil then
562		print "No file"
563		return {}
564	end
565
566	local fh = io.open(file)
567	if fh == nil then
568		print("Failed to open " .. file)
569		return {}
570	end
571
572	local function do_match(nextline, prevline)
573		local pattern, handler, dump
574		for _, v in pairs(pattern_table) do
575			pattern = v.pattern
576			handler = v.process
577			dump = v.dump_prevline
578			if nextline:match(pattern) then
579				if dump and prevline then
580					process_syscall_def(prevline)
581					prevline = nil
582				end
583
584				return handler(nextline, prevline)
585			end
586		end
587
588		abort(1, "Failed to handle: " .. nextline)
589	end
590
591	local prevline
592	for nextline in fh:lines() do
593		-- Strip any comments
594		nextline = nextline:gsub(commentExpr, "")
595		if nextline ~= "" then
596			prevline = do_match(nextline, prevline)
597		end
598	end
599
600	-- Dump any remainder
601	if prevline ~= nil and prevline:find("^[0-9]") then
602		process_syscall_def(prevline)
603	end
604
605	assert(io.close(fh))
606	return capentries
607end
608
609local function get_mask(flags)
610	local mask = 0
611	for _, v in ipairs(flags) do
612		if known_flags[v] == nil then
613			abort(1, "Checking for unknown flag " .. v)
614		end
615
616		mask = mask | known_flags[v]
617	end
618
619	return mask
620end
621
622local function get_mask_pat(pflags)
623	local mask = 0
624	for k, v in pairs(known_flags) do
625		if k:find(pflags) then
626			mask = mask | v
627		end
628	end
629
630	return mask
631end
632
633local function align_sysent_comment(col)
634	write_line("sysent", "\t")
635	col = col + 8 - col % 8
636	while col < 56 do
637		write_line("sysent", "\t")
638		col = col + 8
639	end
640end
641
642local function strip_arg_annotations(arg)
643	arg = arg:gsub("_Contains_[^ ]*[_)] ?", "")
644	arg = arg:gsub("_In[^ ]*[_)] ?", "")
645	arg = arg:gsub("_Out[^ ]*[_)] ?", "")
646	return trim(arg)
647end
648
649local function check_abi_changes(arg)
650	for k, v in pairs(known_abi_flags) do
651		local exprs = v.exprs
652		if abi_changes(k) and exprs ~= nil then
653			for _, e in pairs(exprs) do
654				if arg:find(e) then
655					return true
656				end
657			end
658		end
659	end
660
661	return false
662end
663
664local function process_args(args)
665	local funcargs = {}
666	local changes_abi = false
667
668	for arg in args:gmatch("([^,]+)") do
669		local arg_abi_change = check_abi_changes(arg)
670		changes_abi = changes_abi or arg_abi_change
671
672		arg = strip_arg_annotations(arg)
673
674		local argname = arg:match("([^* ]+)$")
675
676		-- argtype is... everything else.
677		local argtype = trim(arg:gsub(argname .. "$", ""), nil)
678
679		if argtype == "" and argname == "void" then
680			goto out
681		end
682
683		-- is64bittype() needs a bare type so check it after argname
684		-- is removed
685		changes_abi = changes_abi or (abi_changes("pair_64bit") and is64bittype(argtype))
686
687		argtype = argtype:gsub("intptr_t", config.abi_intptr_t)
688		argtype = argtype:gsub("semid_t", config.abi_semid_t)
689		if isptrtype(argtype) then
690			argtype = argtype:gsub("size_t", config.abi_size_t)
691			argtype = argtype:gsub("^long", config.abi_long);
692			argtype = argtype:gsub("^u_long", config.abi_u_long);
693			argtype = argtype:gsub("^const u_long", "const " .. config.abi_u_long);
694		elseif argtype:find("^long$") then
695			argtype = config.abi_long
696		end
697		if isptrarraytype(argtype) and config.abi_ptr_array_t ~= "" then
698			-- `* const *` -> `**`
699			argtype = argtype:gsub("[*][ ]*const[ ]*[*]", "**")
700			-- e.g., `struct aiocb **` -> `uint32_t *`
701			argtype = argtype:gsub("[^*]*[*]", config.abi_ptr_array_t .. " ", 1)
702		end
703
704		-- XX TODO: Forward declarations? See: sysstubfwd in CheriBSD
705		if arg_abi_change then
706			local abi_type_suffix = config.abi_type_suffix
707			argtype = argtype:gsub("(struct [^ ]*)", "%1" ..
708			    abi_type_suffix)
709			argtype = argtype:gsub("(union [^ ]*)", "%1" ..
710			    abi_type_suffix)
711		end
712
713		if abi_changes("pair_64bit") and is64bittype(argtype) then
714			if #funcargs % 2 == 1 then
715				funcargs[#funcargs + 1] = {
716					type = "int",
717					name = "_pad",
718				}
719			end
720			funcargs[#funcargs + 1] = {
721				type = "uint32_t",
722				name = argname .. "1",
723			}
724			funcargs[#funcargs + 1] = {
725				type = "uint32_t",
726				name = argname .. "2",
727			}
728		else
729			funcargs[#funcargs + 1] = {
730				type = argtype,
731				name = argname,
732			}
733		end
734	end
735
736	::out::
737	return funcargs, changes_abi
738end
739
740local function handle_noncompat(sysnum, thr_flag, flags, sysflags, rettype,
741    auditev, syscallret, funcname, funcalias, funcargs, argalias)
742	local argssize
743
744	if flags & known_flags.SYSMUX ~= 0 then
745		argssize = "0"
746	elseif #funcargs > 0 or flags & known_flags.NODEF ~= 0 then
747		argssize = "AS(" .. argalias .. ")"
748	else
749		argssize = "0"
750	end
751
752	write_line("systrace", string.format([[
753	/* %s */
754	case %d: {
755]], funcname, sysnum))
756	write_line("systracetmp", string.format([[
757	/* %s */
758	case %d:
759]], funcname, sysnum))
760	write_line("systraceret", string.format([[
761	/* %s */
762	case %d:
763]], funcname, sysnum))
764
765	if #funcargs > 0 and flags & known_flags.SYSMUX == 0 then
766		write_line("systracetmp", "\t\tswitch (ndx) {\n")
767		write_line("systrace", string.format(
768		    "\t\tstruct %s *p = params;\n", argalias))
769
770
771		local argtype, argname, desc, padding
772		padding = ""
773		for idx, arg in ipairs(funcargs) do
774			argtype = arg.type
775			argname = arg.name
776
777			argtype = trim(argtype:gsub("__restrict$", ""), nil)
778			if argtype == "int" and argname == "_pad" and abi_changes("pair_64bit") then
779				write_line("systracetmp", "#ifdef PAD64_REQUIRED\n")
780			end
781			-- Pointer arg?
782			if argtype:find("*") then
783				desc = "userland " .. argtype
784			else
785				desc = argtype;
786			end
787			write_line("systracetmp", string.format(
788			    "\t\tcase %d%s:\n\t\t\tp = \"%s\";\n\t\t\tbreak;\n",
789			    idx - 1, padding, desc))
790			if argtype == "int" and argname == "_pad" and abi_changes("pair_64bit") then
791				padding = " - _P_"
792				write_line("systracetmp", "#define _P_ 0\n#else\n#define _P_ 1\n#endif\n")
793			end
794
795			if isptrtype(argtype) then
796				write_line("systrace", string.format(
797				    "\t\tuarg[a++] = (%s)p->%s; /* %s */\n",
798				    config.ptr_intptr_t_cast,
799				    argname, argtype))
800			elseif argtype == "union l_semun" then
801				write_line("systrace", string.format(
802				    "\t\tuarg[a++] = p->%s.buf; /* %s */\n",
803				    argname, argtype))
804			elseif argtype:sub(1,1) == "u" or argtype == "size_t" then
805				write_line("systrace", string.format(
806				    "\t\tuarg[a++] = p->%s; /* %s */\n",
807				    argname, argtype))
808			else
809				if argtype == "int" and argname == "_pad" and abi_changes("pair_64bit") then
810					write_line("systrace", "#ifdef PAD64_REQUIRED\n")
811				end
812				write_line("systrace", string.format(
813				    "\t\tiarg[a++] = p->%s; /* %s */\n",
814				    argname, argtype))
815				if argtype == "int" and argname == "_pad" and abi_changes("pair_64bit") then
816					write_line("systrace", "#endif\n")
817				end
818			end
819		end
820
821		write_line("systracetmp",
822		    "\t\tdefault:\n\t\t\tbreak;\n\t\t};\n")
823		if padding ~= "" then
824			write_line("systracetmp", "#undef _P_\n\n")
825		end
826
827		write_line("systraceret", string.format([[
828		if (ndx == 0 || ndx == 1)
829			p = "%s";
830		break;
831]], syscallret))
832	end
833	local n_args = #funcargs
834	if flags & known_flags.SYSMUX ~= 0 then
835		n_args = 0
836	end
837	write_line("systrace", string.format(
838	    "\t\t*n_args = %d;\n\t\tbreak;\n\t}\n", n_args))
839	write_line("systracetmp", "\t\tbreak;\n")
840
841	local nargflags = get_mask({"NOARGS", "NOPROTO", "NODEF"})
842	if flags & nargflags == 0 then
843		if #funcargs > 0 then
844			write_line("sysarg", string.format("struct %s {\n",
845			    argalias))
846			for _, v in ipairs(funcargs) do
847				local argname, argtype = v.name, v.type
848				if argtype == "int" and argname == "_pad" and abi_changes("pair_64bit") then
849					write_line("sysarg", "#ifdef PAD64_REQUIRED\n")
850				end
851				write_line("sysarg", string.format(
852				    "\tchar %s_l_[PADL_(%s)]; %s %s; char %s_r_[PADR_(%s)];\n",
853				    argname, argtype,
854				    argtype, argname,
855				    argname, argtype))
856				if argtype == "int" and argname == "_pad" and abi_changes("pair_64bit") then
857					write_line("sysarg", "#endif\n")
858				end
859			end
860			write_line("sysarg", "};\n")
861		else
862			write_line("sysarg", string.format(
863			    "struct %s {\n\tsyscallarg_t dummy;\n};\n", argalias))
864		end
865	end
866
867	local protoflags = get_mask({"NOPROTO", "NODEF"})
868	if flags & protoflags == 0 then
869		if funcname == "nosys" or funcname == "lkmnosys" or
870		    funcname == "sysarch" or funcname:find("^freebsd") or
871		    funcname:find("^linux") then
872			write_line("sysdcl", string.format(
873			    "%s\t%s(struct thread *, struct %s *)",
874			    rettype, funcname, argalias))
875		else
876			write_line("sysdcl", string.format(
877			    "%s\tsys_%s(struct thread *, struct %s *)",
878			    rettype, funcname, argalias))
879		end
880		write_line("sysdcl", ";\n")
881		write_line("sysaue", string.format("#define\t%sAUE_%s\t%s\n",
882		    config.syscallprefix, funcalias, auditev))
883	end
884
885	write_line("sysent",
886	    string.format("\t{ .sy_narg = %s, .sy_call = (sy_call_t *)", argssize))
887	local column = 8 + 2 + #argssize + 15
888
889	if flags & known_flags.SYSMUX ~= 0 then
890		write_line("sysent", string.format(
891		    "nosys, .sy_auevent = AUE_NULL, " ..
892		    ".sy_flags = %s, .sy_thrcnt = SY_THR_STATIC },",
893		    sysflags))
894		column = column + #"nosys" + #"AUE_NULL" + 3
895	elseif flags & known_flags.NOSTD ~= 0 then
896		write_line("sysent", string.format(
897		    "lkmressys, .sy_auevent = AUE_NULL, " ..
898		    ".sy_flags = %s, .sy_thrcnt = SY_THR_ABSENT },",
899		    sysflags))
900		column = column + #"lkmressys" + #"AUE_NULL" + 3
901	else
902		if funcname == "nosys" or funcname == "lkmnosys" or
903		    funcname == "sysarch" or funcname:find("^freebsd") or
904		    funcname:find("^linux") then
905			write_line("sysent", string.format(
906			    "%s, .sy_auevent = %s, .sy_flags = %s, .sy_thrcnt = %s },",
907			    funcname, auditev, sysflags, thr_flag))
908			column = column + #funcname + #auditev + #sysflags + 3
909		else
910			write_line("sysent", string.format(
911			    "sys_%s, .sy_auevent = %s, .sy_flags = %s, .sy_thrcnt = %s },",
912			    funcname, auditev, sysflags, thr_flag))
913			column = column + #funcname + #auditev + #sysflags + 7
914		end
915	end
916
917	align_sysent_comment(column)
918	write_line("sysent", string.format("/* %d = %s */\n",
919	    sysnum, funcalias))
920	write_line("sysnames", string.format("\t\"%s\",\t\t\t/* %d = %s */\n",
921	    funcalias, sysnum, funcalias))
922
923	if flags & known_flags.NODEF == 0 then
924		write_line("syshdr", string.format("#define\t%s%s\t%d\n",
925		    config.syscallprefix, funcalias, sysnum))
926		write_line("sysmk", string.format(" \\\n\t%s.o",
927		    funcalias))
928	end
929end
930
931local function handle_obsol(sysnum, funcname, comment)
932	write_line("sysent",
933	    "\t{ .sy_narg = 0, .sy_call = (sy_call_t *)nosys, " ..
934	    ".sy_auevent = AUE_NULL, .sy_flags = 0, .sy_thrcnt = SY_THR_ABSENT },")
935	align_sysent_comment(34)
936
937	write_line("sysent", string.format("/* %d = obsolete %s */\n",
938	    sysnum, comment))
939	write_line("sysnames", string.format(
940	    "\t\"obs_%s\",\t\t\t/* %d = obsolete %s */\n",
941	    funcname, sysnum, comment))
942	write_line("syshdr", string.format("\t\t\t\t/* %d is obsolete %s */\n",
943	    sysnum, comment))
944end
945
946local function handle_compat(sysnum, thr_flag, flags, sysflags, rettype,
947    auditev, funcname, funcalias, funcargs, argalias)
948	local argssize, out, outdcl, wrap, prefix, descr
949
950	if #funcargs > 0 or flags & known_flags.NODEF ~= 0 then
951		argssize = "AS(" .. argalias .. ")"
952	else
953		argssize = "0"
954	end
955
956	for _, v in pairs(compat_options) do
957		if flags & v.mask ~= 0 then
958			if config.mincompat > v.compatlevel then
959				funcname = strip_abi_prefix(funcname)
960				funcname = v.prefix .. funcname
961				return handle_obsol(sysnum, funcname, funcname)
962			end
963			v.count = v.count + 1
964			out = v.tmp
965			outdcl = v.dcltmp
966			wrap = v.flag:lower()
967			prefix = v.prefix
968			descr = v.descr
969			goto compatdone
970		end
971	end
972
973	::compatdone::
974	local dprotoflags = get_mask({"NOPROTO", "NODEF"})
975	local nargflags = dprotoflags | known_flags.NOARGS
976	if #funcargs > 0 and flags & nargflags == 0 then
977		write_line(out, string.format("struct %s {\n", argalias))
978		for _, v in ipairs(funcargs) do
979			local argname, argtype = v.name, v.type
980			write_line(out, string.format(
981			    "\tchar %s_l_[PADL_(%s)]; %s %s; char %s_r_[PADR_(%s)];\n",
982			    argname, argtype,
983			    argtype, argname,
984			    argname, argtype))
985		end
986		write_line(out, "};\n")
987	elseif flags & nargflags == 0 then
988		write_line("sysarg", string.format(
989		    "struct %s {\n\tsyscallarg_t dummy;\n};\n", argalias))
990	end
991	if flags & dprotoflags == 0 then
992		write_line(outdcl, string.format(
993		    "%s\t%s%s(struct thread *, struct %s *);\n",
994		    rettype, prefix, funcname, argalias))
995		write_line("sysaue", string.format(
996		    "#define\t%sAUE_%s%s\t%s\n", config.syscallprefix,
997		    prefix, funcname, auditev))
998	end
999
1000	if flags & known_flags.NOSTD ~= 0 then
1001		write_line("sysent", string.format(
1002		    "\t{ .sy_narg = %s, .sy_call = (sy_call_t *)%s, " ..
1003		    ".sy_auevent = %s, .sy_flags = 0, " ..
1004		    ".sy_thrcnt = SY_THR_ABSENT },",
1005		    "0", "lkmressys", "AUE_NULL"))
1006		align_sysent_comment(8 + 2 + #"0" + 15 + #"lkmressys" +
1007		    #"AUE_NULL" + 3)
1008	else
1009		write_line("sysent", string.format(
1010		    "\t{ %s(%s,%s), .sy_auevent = %s, .sy_flags = %s, .sy_thrcnt = %s },",
1011		    wrap, argssize, funcname, auditev, sysflags, thr_flag))
1012		align_sysent_comment(8 + 9 + #argssize + 1 + #funcname +
1013		    #auditev + #sysflags + 4)
1014	end
1015
1016	write_line("sysent", string.format("/* %d = %s %s */\n",
1017	    sysnum, descr, funcalias))
1018	write_line("sysnames", string.format(
1019	    "\t\"%s.%s\",\t\t/* %d = %s %s */\n",
1020	    wrap, funcalias, sysnum, descr, funcalias))
1021	-- Do not provide freebsdN_* symbols in libc for < FreeBSD 7
1022	local nosymflags = get_mask({"COMPAT", "COMPAT4", "COMPAT6"})
1023	if flags & nosymflags ~= 0 then
1024		write_line("syshdr", string.format(
1025		    "\t\t\t\t/* %d is %s %s */\n",
1026		    sysnum, descr, funcalias))
1027	elseif flags & known_flags.NODEF == 0 then
1028		write_line("syshdr", string.format("#define\t%s%s%s\t%d\n",
1029		    config.syscallprefix, prefix, funcalias, sysnum))
1030		write_line("sysmk", string.format(" \\\n\t%s%s.o",
1031		    prefix, funcalias))
1032	end
1033end
1034
1035local function handle_unimpl(sysnum, sysstart, sysend, comment)
1036	if sysstart == nil and sysend == nil then
1037		sysstart = tonumber(sysnum)
1038		sysend = tonumber(sysnum)
1039	end
1040
1041	sysnum = sysstart
1042	while sysnum <= sysend do
1043		write_line("sysent", string.format(
1044		    "\t{ .sy_narg = 0, .sy_call = (sy_call_t *)nosys, " ..
1045		    ".sy_auevent = AUE_NULL, .sy_flags = 0, " ..
1046		    ".sy_thrcnt = SY_THR_ABSENT },\t\t\t/* %d = %s */\n",
1047		    sysnum, comment))
1048		write_line("sysnames", string.format(
1049		    "\t\"#%d\",\t\t\t/* %d = %s */\n",
1050		    sysnum, sysnum, comment))
1051		sysnum = sysnum + 1
1052	end
1053end
1054
1055local function handle_reserved(sysnum, sysstart, sysend)
1056	handle_unimpl(sysnum, sysstart, sysend, "reserved for local use")
1057end
1058
1059process_syscall_def = function(line)
1060	local sysstart, sysend, flags, funcname, sysflags
1061	local thr_flag, syscallret
1062	local orig = line
1063	flags = 0
1064	thr_flag = "SY_THR_STATIC"
1065
1066	-- Parse out the interesting information first
1067	local initialExpr = "^([^%s]+)%s+([^%s]+)%s+([^%s]+)%s*"
1068	local sysnum, auditev, allflags = line:match(initialExpr)
1069
1070	if sysnum == nil or auditev == nil or allflags == nil then
1071		-- XXX TODO: Better?
1072		abort(1, "Completely malformed: " .. line)
1073	end
1074
1075	if sysnum:find("-") then
1076		sysstart, sysend = sysnum:match("^([%d]+)-([%d]+)$")
1077		if sysstart == nil or sysend == nil then
1078			abort(1, "Malformed range: " .. sysnum)
1079		end
1080		sysnum = nil
1081		sysstart = tonumber(sysstart)
1082		sysend = tonumber(sysend)
1083		if sysstart ~= maxsyscall + 1 then
1084			abort(1, "syscall number out of sync, missing " ..
1085			    maxsyscall + 1)
1086		end
1087	else
1088		sysnum = tonumber(sysnum)
1089		if sysnum ~= maxsyscall + 1 then
1090			abort(1, "syscall number out of sync, missing " ..
1091			    maxsyscall + 1)
1092		end
1093	end
1094
1095	-- Split flags
1096	for flag in allflags:gmatch("([^|]+)") do
1097		if known_flags[flag] == nil then
1098			abort(1, "Unknown flag " .. flag .. " for " ..  sysnum)
1099		end
1100		flags = flags | known_flags[flag]
1101	end
1102
1103	if (flags & get_mask({"RESERVED", "UNIMPL"})) == 0 and sysnum == nil then
1104		abort(1, "Range only allowed with RESERVED and UNIMPL: " .. line)
1105	end
1106
1107	if (flags & known_flags.NOTSTATIC) ~= 0 then
1108		thr_flag = "SY_THR_ABSENT"
1109	end
1110
1111	-- Strip earlier bits out, leave declaration + alt
1112	line = line:gsub("^.+" .. allflags .. "%s*", "")
1113
1114	local decl_fnd = line:find("^{") ~= nil
1115	if decl_fnd and line:find("}") == nil then
1116		abort(1, "Malformed, no closing brace: " .. line)
1117	end
1118
1119	local decl, alt
1120	if decl_fnd then
1121		line = line:gsub("^{", "")
1122		decl, alt = line:match("([^}]*)}[%s]*(.*)$")
1123	else
1124		alt = line
1125	end
1126
1127	if decl == nil and alt == nil then
1128		abort(1, "Malformed bits: " .. line)
1129	end
1130
1131	local funcalias, funcomment, argalias, rettype, args
1132	if not decl_fnd and alt ~= nil and alt ~= "" then
1133		-- Peel off one entry for name
1134		funcname = trim(alt:match("^([^%s]+)"), nil)
1135		alt = alt:gsub("^([^%s]+)[%s]*", "")
1136	end
1137	-- Do we even need it?
1138	if flags & get_mask({"OBSOL", "UNIMPL"}) ~= 0 then
1139		local NF = 0
1140		for _ in orig:gmatch("[^%s]+") do
1141			NF = NF + 1
1142		end
1143
1144		funcomment = funcname or ''
1145		if NF < 6 then
1146			funcomment = funcomment .. " " .. alt
1147		end
1148
1149		funcomment = trim(funcomment)
1150
1151--		if funcname ~= nil then
1152--		else
1153--			funcomment = trim(alt)
1154--		end
1155		goto skipalt
1156	end
1157
1158	if alt ~= nil and alt ~= "" then
1159		local altExpr = "^([^%s]+)%s+([^%s]+)%s+([^%s]+)"
1160		funcalias, argalias, rettype = alt:match(altExpr)
1161		funcalias = trim(funcalias)
1162		if funcalias == nil or argalias == nil or rettype == nil then
1163			abort(1, "Malformed alt: " .. line)
1164		end
1165	end
1166	if decl_fnd then
1167		-- Don't clobber rettype set in the alt information
1168		if rettype == nil then
1169			rettype = "int"
1170		end
1171		-- Peel off the return type
1172		syscallret = line:match("([^%s]+)%s")
1173		line = line:match("[^%s]+%s(.+)")
1174		-- Pointer incoming
1175		if line:sub(1,1) == "*" then
1176			syscallret = syscallret .. " "
1177		end
1178		while line:sub(1,1) == "*" do
1179			line = line:sub(2)
1180			syscallret = syscallret .. "*"
1181		end
1182		funcname = line:match("^([^(]+)%(")
1183		if funcname == nil then
1184			abort(1, "Not a signature? " .. line)
1185		end
1186		args = line:match("^[^(]+%((.+)%)[^)]*$")
1187		args = trim(args, '[,%s]')
1188	end
1189
1190	::skipalt::
1191
1192	if funcname == nil then
1193		funcname = funcalias
1194	end
1195
1196	funcname = trim(funcname)
1197
1198	if config.obsol_dict[funcname] then
1199		local compat_prefix = ""
1200		for _, v in pairs(compat_options) do
1201			if flags & v.mask ~= 0 then
1202				compat_prefix = v.prefix
1203				goto obsol_compat_done
1204			end
1205		end
1206		::obsol_compat_done::
1207		args = nil
1208		flags = known_flags.OBSOL
1209		funcomment = compat_prefix .. funcname
1210	end
1211	if config.unimpl_dict[funcname] then
1212		flags = known_flags.UNIMPL
1213		funcomment = funcname
1214	end
1215
1216	sysflags = "0"
1217
1218	-- NODEF events do not get audited
1219	if flags & known_flags.NODEF ~= 0 then
1220		auditev = 'AUE_NULL'
1221	end
1222
1223	-- If applicable; strip the ABI prefix from the name
1224	local stripped_name = strip_abi_prefix(funcname)
1225
1226	if flags & known_flags.CAPENABLED ~= 0 or
1227	    config.capenabled[funcname] ~= nil or
1228	    config.capenabled[stripped_name] ~= nil then
1229		sysflags = "SYF_CAPENABLED"
1230	end
1231
1232	local funcargs = {}
1233	local changes_abi = false
1234	if args ~= nil then
1235		funcargs, changes_abi = process_args(args)
1236	end
1237	if config.sys_no_abi_change[funcname] then
1238		changes_abi = false
1239	end
1240	local noproto = config.abi_flags ~= "" and not changes_abi
1241
1242	local argprefix = ''
1243	local funcprefix = ''
1244	if abi_changes("pointer_args") then
1245		for _, v in ipairs(funcargs) do
1246			if isptrtype(v.type) then
1247				if config.sys_no_abi_change[funcname] then
1248					print("WARNING: " .. funcname ..
1249					    " in syscall_no_abi_change, but pointers args are present")
1250				end
1251				changes_abi = true
1252				goto ptrfound
1253			end
1254		end
1255		::ptrfound::
1256	end
1257	if config.sys_abi_change[funcname] then
1258		changes_abi = true
1259	end
1260	if changes_abi then
1261		-- argalias should be:
1262		--   COMPAT_PREFIX + ABI Prefix + funcname
1263		argprefix = config.abi_func_prefix
1264		funcprefix = config.abi_func_prefix
1265		funcalias = funcprefix .. funcname
1266		noproto = false
1267	end
1268	if funcname ~= nil then
1269		funcname = funcprefix .. funcname
1270	end
1271	if funcalias == nil or funcalias == "" then
1272		funcalias = funcname
1273	end
1274
1275	if argalias == nil and funcname ~= nil then
1276		argalias = funcname .. "_args"
1277		for _, v in pairs(compat_options) do
1278			local mask = v.mask
1279			if (flags & mask) ~= 0 then
1280				-- Multiple aliases doesn't seem to make
1281				-- sense.
1282				argalias = v.prefix .. argalias
1283				goto out
1284			end
1285		end
1286		::out::
1287	elseif argalias ~= nil then
1288		argalias = argprefix .. argalias
1289	end
1290
1291	local ncompatflags = get_mask({"STD", "NODEF", "NOARGS", "NOPROTO",
1292	    "NOSTD"})
1293	local compatflags = get_mask_pat("COMPAT.*")
1294	if noproto or flags & known_flags.SYSMUX ~= 0 then
1295		flags = flags | known_flags.NOPROTO;
1296	end
1297	if flags & known_flags.OBSOL ~= 0 then
1298		handle_obsol(sysnum, funcname, funcomment)
1299	elseif flags & known_flags.RESERVED ~= 0 then
1300		handle_reserved(sysnum, sysstart, sysend)
1301	elseif flags & known_flags.UNIMPL ~= 0 then
1302		handle_unimpl(sysnum, sysstart, sysend, funcomment)
1303	elseif flags & compatflags ~= 0 then
1304		if flags & known_flags.STD ~= 0 then
1305			abort(1, "Incompatible COMPAT/STD: " .. line)
1306		end
1307		handle_compat(sysnum, thr_flag, flags, sysflags, rettype,
1308		    auditev, funcname, funcalias, funcargs, argalias)
1309	elseif flags & ncompatflags ~= 0 then
1310		handle_noncompat(sysnum, thr_flag, flags, sysflags, rettype,
1311		    auditev, syscallret, funcname, funcalias, funcargs,
1312		    argalias)
1313	else
1314		abort(1, "Bad flags? " .. line)
1315	end
1316
1317	if sysend ~= nil then
1318		maxsyscall = sysend
1319	elseif sysnum ~= nil then
1320		maxsyscall = sysnum
1321	end
1322end
1323
1324-- Entry point
1325
1326if #arg < 1 or #arg > 2 then
1327	error("usage: " .. arg[0] .. " input-file <config-file>")
1328end
1329
1330local sysfile, configfile = arg[1], arg[2]
1331
1332-- process_config either returns nil and a message, or a
1333-- table that we should merge into the global config
1334if configfile ~= nil then
1335	local res = assert(process_config(configfile))
1336
1337	for k, v in pairs(res) do
1338		if v ~= config[k] then
1339			config[k] = v
1340			config_modified[k] = true
1341		end
1342	end
1343end
1344
1345local compat_set = config.compat_set
1346if compat_set ~= "" then
1347	if not compat_option_sets[compat_set] then
1348		abort(1, "Undefined compat set: " .. compat_set)
1349	end
1350
1351	compat_options = compat_option_sets[compat_set]
1352else
1353	compat_options = {}
1354end
1355
1356-- We ignore errors here if we're relying on the default configuration.
1357if not config_modified.capenabled then
1358	config.capenabled = grab_capenabled(config.capabilities_conf,
1359	    config_modified.capabilities_conf == nil)
1360elseif config.capenabled ~= "" then
1361	-- Due to limitations in the config format mostly, we'll have a comma
1362	-- separated list.  Parse it into lines
1363	local capenabled = {}
1364	-- print("here: " .. config.capenabled)
1365	for sysc in config.capenabled:gmatch("([^,]+)") do
1366		capenabled[sysc] = true
1367	end
1368	config.capenabled = capenabled
1369end
1370process_compat()
1371process_abi_flags()
1372process_syscall_abi_change()
1373process_obsol()
1374process_unimpl()
1375
1376if not lfs.mkdir(tmpspace) then
1377	error("Failed to create tempdir " .. tmpspace)
1378end
1379
1380-- XXX Revisit the error handling here, we should probably move the rest of this
1381-- into a function that we pcall() so we can catch the errors and clean up
1382-- gracefully.
1383for _, v in ipairs(temp_files) do
1384	local tmpname = tmpspace .. v
1385	files[v] = io.open(tmpname, "w+")
1386	-- XXX Revisit these with a pcall() + error handler
1387	if not files[v] then
1388		abort(1, "Failed to open temp file: " .. tmpname)
1389	end
1390end
1391
1392for _, v in ipairs(output_files) do
1393	local tmpname = tmpspace .. v
1394	files[v] = io.open(tmpname, "w+")
1395	-- XXX Revisit these with a pcall() + error handler
1396	if not files[v] then
1397		abort(1, "Failed to open temp output file: " .. tmpname)
1398	end
1399end
1400
1401-- Write out all of the preamble bits
1402write_line("sysent", string.format([[
1403
1404/* The casts are bogus but will do for now. */
1405struct sysent %s[] = {
1406]], config.switchname))
1407
1408write_line("syssw", string.format([[/*
1409 * System call switch table.
1410 *
1411 * DO NOT EDIT-- this file is automatically %s.
1412 * $%s$
1413 */
1414
1415]], generated_tag, config.os_id_keyword))
1416
1417write_line("sysarg", string.format([[/*
1418 * System call prototypes.
1419 *
1420 * DO NOT EDIT-- this file is automatically %s.
1421 * $%s$
1422 */
1423
1424#ifndef %s
1425#define	%s
1426
1427#include <sys/signal.h>
1428#include <sys/acl.h>
1429#include <sys/cpuset.h>
1430#include <sys/domainset.h>
1431#include <sys/_ffcounter.h>
1432#include <sys/_semaphore.h>
1433#include <sys/ucontext.h>
1434#include <sys/wait.h>
1435
1436#include <bsm/audit_kevents.h>
1437
1438struct proc;
1439
1440struct thread;
1441
1442#define	PAD_(t)	(sizeof(syscallarg_t) <= sizeof(t) ? \
1443		0 : sizeof(syscallarg_t) - sizeof(t))
1444
1445#if BYTE_ORDER == LITTLE_ENDIAN
1446#define	PADL_(t)	0
1447#define	PADR_(t)	PAD_(t)
1448#else
1449#define	PADL_(t)	PAD_(t)
1450#define	PADR_(t)	0
1451#endif
1452
1453]], generated_tag, config.os_id_keyword, config.sysproto_h,
1454    config.sysproto_h))
1455if abi_changes("pair_64bit") then
1456	write_line("sysarg", string.format([[
1457#if !defined(PAD64_REQUIRED) && !defined(__amd64__)
1458#define PAD64_REQUIRED
1459#endif
1460]]))
1461end
1462if abi_changes("pair_64bit") then
1463	write_line("systrace", string.format([[
1464#if !defined(PAD64_REQUIRED) && !defined(__amd64__)
1465#define PAD64_REQUIRED
1466#endif
1467]]))
1468end
1469for _, v in pairs(compat_options) do
1470	write_line(v.tmp, string.format("\n#ifdef %s\n\n", v.definition))
1471end
1472
1473write_line("sysnames", string.format([[/*
1474 * System call names.
1475 *
1476 * DO NOT EDIT-- this file is automatically %s.
1477 * $%s$
1478 */
1479
1480const char *%s[] = {
1481]], generated_tag, config.os_id_keyword, config.namesname))
1482
1483write_line("syshdr", string.format([[/*
1484 * System call numbers.
1485 *
1486 * DO NOT EDIT-- this file is automatically %s.
1487 * $%s$
1488 */
1489
1490]], generated_tag, config.os_id_keyword))
1491
1492write_line("sysmk", string.format([[# FreeBSD system call object files.
1493# DO NOT EDIT-- this file is automatically %s.
1494# $%s$
1495MIASM = ]], generated_tag, config.os_id_keyword))
1496
1497write_line("systrace", string.format([[/*
1498 * System call argument to DTrace register array converstion.
1499 *
1500 * DO NOT EDIT-- this file is automatically %s.
1501 * $%s$
1502 * This file is part of the DTrace syscall provider.
1503 */
1504
1505static void
1506systrace_args(int sysnum, void *params, uint64_t *uarg, int *n_args)
1507{
1508	int64_t *iarg = (int64_t *)uarg;
1509	int a = 0;
1510	switch (sysnum) {
1511]], generated_tag, config.os_id_keyword))
1512
1513write_line("systracetmp", [[static void
1514systrace_entry_setargdesc(int sysnum, int ndx, char *desc, size_t descsz)
1515{
1516	const char *p = NULL;
1517	switch (sysnum) {
1518]])
1519
1520write_line("systraceret", [[static void
1521systrace_return_setargdesc(int sysnum, int ndx, char *desc, size_t descsz)
1522{
1523	const char *p = NULL;
1524	switch (sysnum) {
1525]])
1526
1527-- Processing the sysfile will parse out the preprocessor bits and put them into
1528-- the appropriate place.  Any syscall-looking lines get thrown into the sysfile
1529-- buffer, one per line, for later processing once they're all glued together.
1530process_sysfile(sysfile)
1531
1532write_line("sysinc",
1533    "\n#define AS(name) (sizeof(struct name) / sizeof(syscallarg_t))\n")
1534
1535for _, v in pairs(compat_options) do
1536	if v.count > 0 then
1537		write_line("sysinc", string.format([[
1538
1539#ifdef %s
1540#define %s(n, name) .sy_narg = n, .sy_call = (sy_call_t *)__CONCAT(%s, name)
1541#else
1542#define %s(n, name) .sy_narg = 0, .sy_call = (sy_call_t *)nosys
1543#endif
1544]], v.definition, v.flag:lower(), v.prefix, v.flag:lower()))
1545	end
1546
1547	write_line(v.dcltmp, string.format("\n#endif /* %s */\n\n",
1548	    v.definition))
1549end
1550
1551write_line("sysprotoend", string.format([[
1552
1553#undef PAD_
1554#undef PADL_
1555#undef PADR_
1556
1557#endif /* !%s */
1558]], config.sysproto_h))
1559
1560write_line("sysmk", "\n")
1561write_line("sysent", "};\n")
1562write_line("sysnames", "};\n")
1563-- maxsyscall is the highest seen; MAXSYSCALL should be one higher
1564write_line("syshdr", string.format("#define\t%sMAXSYSCALL\t%d\n",
1565    config.syscallprefix, maxsyscall + 1))
1566write_line("systrace", [[
1567	default:
1568		*n_args = 0;
1569		break;
1570	};
1571}
1572]])
1573
1574write_line("systracetmp", [[
1575	default:
1576		break;
1577	};
1578	if (p != NULL)
1579		strlcpy(desc, p, descsz);
1580}
1581]])
1582
1583write_line("systraceret", [[
1584	default:
1585		break;
1586	};
1587	if (p != NULL)
1588		strlcpy(desc, p, descsz);
1589}
1590]])
1591
1592-- Finish up; output
1593write_line("syssw", read_file("sysinc"))
1594write_line("syssw", read_file("sysent"))
1595
1596write_line("sysproto", read_file("sysarg"))
1597write_line("sysproto", read_file("sysdcl"))
1598for _, v in pairs(compat_options) do
1599	write_line("sysproto", read_file(v.tmp))
1600	write_line("sysproto", read_file(v.dcltmp))
1601end
1602write_line("sysproto", read_file("sysaue"))
1603write_line("sysproto", read_file("sysprotoend"))
1604
1605write_line("systrace", read_file("systracetmp"))
1606write_line("systrace", read_file("systraceret"))
1607
1608for _, v in ipairs(output_files) do
1609	local target = config[v]
1610	if target ~= "/dev/null" then
1611		local fh = assert(io.open(target, "w+"))
1612		if fh == nil then
1613			abort(1, "Failed to open '" .. target .. "'")
1614		end
1615		assert(fh:write(read_file(v)))
1616		assert(fh:close())
1617	end
1618end
1619
1620cleanup()
1621