xref: /freebsd/sys/tools/makesyscalls.lua (revision 06c3fb27)
1--
2-- SPDX-License-Identifier: BSD-2-Clause
3--
4-- Copyright (c) 2019 Kyle Evans <kevans@FreeBSD.org>
5--
6-- Redistribution and use in source and binary forms, with or without
7-- modification, are permitted provided that the following conditions
8-- are met:
9-- 1. Redistributions of source code must retain the above copyright
10--    notice, this list of conditions and the following disclaimer.
11-- 2. Redistributions in binary form must reproduce the above copyright
12--    notice, this list of conditions and the following disclaimer in the
13--    documentation and/or other materials provided with the distribution.
14--
15-- THIS SOFTWARE IS PROVIDED BY THE AUTHOR AND CONTRIBUTORS ``AS IS'' AND
16-- ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE
17-- IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE
18-- ARE DISCLAIMED.  IN NO EVENT SHALL THE AUTHOR OR CONTRIBUTORS BE LIABLE
19-- FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL
20-- DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS
21-- OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION)
22-- HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
23-- LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY
24-- OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF
25-- SUCH DAMAGE.
26--
27
28
29-- We generally assume that this script will be run by flua, however we've
30-- carefully crafted modules for it that mimic interfaces provided by modules
31-- available in ports.  Currently, this script is compatible with lua from ports
32-- along with the compatible luafilesystem and lua-posix modules.
33local lfs = require("lfs")
34local unistd = require("posix.unistd")
35
36local savesyscall = -1
37local maxsyscall = -1
38local generated_tag = "@" .. "generated"
39
40-- Default configuration; any of these may get replaced by a configuration file
41-- optionally specified.
42local config = {
43	os_id_keyword = "FreeBSD",		-- obsolete, ignored on input, not generated
44	abi_func_prefix = "",
45	sysnames = "syscalls.c",
46	sysproto = "../sys/sysproto.h",
47	sysproto_h = "_SYS_SYSPROTO_H_",
48	syshdr = "../sys/syscall.h",
49	sysmk = "/dev/null",
50	syssw = "init_sysent.c",
51	syscallprefix = "SYS_",
52	switchname = "sysent",
53	namesname = "syscallnames",
54	systrace = "systrace_args.c",
55	capabilities_conf = "capabilities.conf",
56	capenabled = {},
57	compat_set = "native",
58	mincompat = 0,
59	abi_type_suffix = "",
60	abi_flags = "",
61	abi_flags_mask = 0,
62	abi_headers = "",
63	abi_intptr_t = "intptr_t",
64	abi_size_t = "size_t",
65	abi_u_long = "u_long",
66	abi_long = "long",
67	abi_semid_t = "semid_t",
68	abi_ptr_array_t = "",
69	ptr_intptr_t_cast = "intptr_t",
70	syscall_abi_change = "",
71	sys_abi_change = {},
72	syscall_no_abi_change = "",
73	sys_no_abi_change = {},
74	obsol = "",
75	obsol_dict = {},
76	unimpl = "",
77	unimpl_dict = {},
78}
79
80local config_modified = {}
81local cleantmp = true
82local tmpspace = "/tmp/sysent." .. unistd.getpid() .. "/"
83
84local output_files = {
85	"sysnames",
86	"syshdr",
87	"sysmk",
88	"syssw",
89	"systrace",
90	"sysproto",
91}
92
93-- These ones we'll create temporary files for; generation purposes.
94local temp_files = {
95	"sysaue",
96	"sysdcl",
97	"syscompat",
98	"syscompatdcl",
99	"sysent",
100	"sysinc",
101	"sysarg",
102	"sysprotoend",
103	"systracetmp",
104	"systraceret",
105}
106
107-- Opened files
108local files = {}
109
110local function cleanup()
111	for _, v in pairs(files) do
112		assert(v:close())
113	end
114	if cleantmp then
115		if lfs.dir(tmpspace) then
116			for fname in lfs.dir(tmpspace) do
117				if fname ~= "." and fname ~= ".." then
118					assert(os.remove(tmpspace .. "/" ..
119					    fname))
120				end
121			end
122		end
123
124		if lfs.attributes(tmpspace) and not lfs.rmdir(tmpspace) then
125			assert(io.stderr:write("Failed to clean up tmpdir: " ..
126			    tmpspace .. "\n"))
127		end
128	else
129		assert(io.stderr:write("Temp files left in " .. tmpspace ..
130		    "\n"))
131	end
132end
133
134local function abort(status, msg)
135	assert(io.stderr:write(msg .. "\n"))
136	cleanup()
137	os.exit(status)
138end
139
140-- Each entry should have a value so we can represent abi flags as a bitmask
141-- for convenience.  One may also optionally provide an expr; this gets applied
142-- to each argument type to indicate whether this argument is subject to ABI
143-- change given the configured flags.
144local known_abi_flags = {
145	long_size = {
146		value	= 0x00000001,
147		exprs	= {
148			"_Contains[a-z_]*_long_",
149			"^long [a-z0-9_]+$",
150			"long [*]",
151			"size_t [*]",
152			-- semid_t is not included because it is only used
153			-- as an argument or written out individually and
154			-- said writes are handled by the ksem framework.
155			-- Technically a sign-extension issue exists for
156			-- arguments, but because semid_t is actually a file
157			-- descriptor negative 32-bit values are invalid
158			-- regardless of sign-extension.
159		},
160	},
161	time_t_size = {
162		value	= 0x00000002,
163		exprs	= {
164			"_Contains[a-z_]*_timet_",
165		},
166	},
167	pointer_args = {
168		value	= 0x00000004,
169	},
170	pointer_size = {
171		value	= 0x00000008,
172		exprs	= {
173			"_Contains[a-z_]*_ptr_",
174			"[*][*]",
175		},
176	},
177	pair_64bit = {
178		value	= 0x00000010,
179		exprs	= {
180			"^dev_t[ ]*$",
181			"^id_t[ ]*$",
182			"^off_t[ ]*$",
183		},
184	},
185}
186
187local known_flags = {
188	STD		= 0x00000001,
189	OBSOL		= 0x00000002,
190	RESERVED	= 0x00000004,
191	UNIMPL		= 0x00000008,
192	NODEF		= 0x00000010,
193	NOARGS		= 0x00000020,
194	NOPROTO		= 0x00000040,
195	NOSTD		= 0x00000080,
196	NOTSTATIC	= 0x00000100,
197	CAPENABLED	= 0x00000200,
198	SYSMUX		= 0x00000400,
199
200	-- Compat flags start from here.  We have plenty of space.
201}
202
203-- All compat option entries should have five entries:
204--	definition: The preprocessor macro that will be set for this
205--	compatlevel: The level this compatibility should be included at.  This
206--	    generally represents the version of FreeBSD that it is compatible
207--	    with, but ultimately it's just the level of mincompat in which it's
208--	    included.
209--	flag: The name of the flag in syscalls.master.
210--	prefix: The prefix to use for _args and syscall prototype.  This will be
211--	    used as-is, without "_" or any other character appended.
212--	descr: The description of this compat option in init_sysent.c comments.
213-- The special "stdcompat" entry will cause the other five to be autogenerated.
214local compat_option_sets = {
215	native = {
216		{
217			definition = "COMPAT_43",
218			compatlevel = 3,
219			flag = "COMPAT",
220			prefix = "o",
221			descr = "old",
222		},
223		{ stdcompat = "FREEBSD4" },
224		{ stdcompat = "FREEBSD6" },
225		{ stdcompat = "FREEBSD7" },
226		{ stdcompat = "FREEBSD10" },
227		{ stdcompat = "FREEBSD11" },
228		{ stdcompat = "FREEBSD12" },
229		{ stdcompat = "FREEBSD13" },
230		{ stdcompat = "FREEBSD14" },
231	},
232}
233
234-- compat_options will be resolved to a set from the configuration.
235local compat_options
236
237local function trim(s, char)
238	if s == nil then
239		return nil
240	end
241	if char == nil then
242		char = "%s"
243	end
244	return s:gsub("^" .. char .. "+", ""):gsub(char .. "+$", "")
245end
246
247-- config looks like a shell script; in fact, the previous makesyscalls.sh
248-- script actually sourced it in.  It had a pretty common format, so we should
249-- be fine to make various assumptions
250local function process_config(file)
251	local cfg = {}
252	local comment_line_expr = "^%s*#.*"
253	-- We capture any whitespace padding here so we can easily advance to
254	-- the end of the line as needed to check for any trailing bogus bits.
255	-- Alternatively, we could drop the whitespace and instead try to
256	-- use a pattern to strip out the meaty part of the line, but then we
257	-- would need to sanitize the line for potentially special characters.
258	local line_expr = "^([%w%p]+%s*)=(%s*[`\"]?[^\"`]*[`\"]?)"
259
260	if not file then
261		return nil, "No file given"
262	end
263
264	local fh = assert(io.open(file))
265
266	for nextline in fh:lines() do
267		-- Strip any whole-line comments
268		nextline = nextline:gsub(comment_line_expr, "")
269		-- Parse it into key, value pairs
270		local key, value = nextline:match(line_expr)
271		if key ~= nil and value ~= nil then
272			local kvp = key .. "=" .. value
273			key = trim(key)
274			value = trim(value)
275			local delim = value:sub(1,1)
276			if delim == '"' then
277				local trailing_context
278
279				-- Strip off the key/value part
280				trailing_context = nextline:sub(kvp:len() + 1)
281				-- Strip off any trailing comment
282				trailing_context = trailing_context:gsub("#.*$",
283				    "")
284				-- Strip off leading/trailing whitespace
285				trailing_context = trim(trailing_context)
286				if trailing_context ~= "" then
287					print(trailing_context)
288					abort(1, "Malformed line: " .. nextline)
289				end
290
291				value = trim(value, delim)
292			else
293				-- Strip off potential comments
294				value = value:gsub("#.*$", "")
295				-- Strip off any padding whitespace
296				value = trim(value)
297				if value:match("%s") then
298					abort(1, "Malformed config line: " ..
299					    nextline)
300				end
301			end
302			cfg[key] = value
303		elseif not nextline:match("^%s*$") then
304			-- Make sure format violations don't get overlooked
305			-- here, but ignore blank lines.  Comments are already
306			-- stripped above.
307			abort(1, "Malformed config line: " .. nextline)
308		end
309	end
310
311	assert(io.close(fh))
312	return cfg
313end
314
315local function grab_capenabled(file, open_fail_ok)
316	local capentries = {}
317	local commentExpr = "#.*"
318
319	if file == nil then
320		print "No file"
321		return {}
322	end
323
324	local fh = io.open(file)
325	if fh == nil then
326		if not open_fail_ok then
327			abort(1, "Failed to open " .. file)
328		end
329		return {}
330	end
331
332	for nextline in fh:lines() do
333		-- Strip any comments
334		nextline = nextline:gsub(commentExpr, "")
335		if nextline ~= "" then
336			capentries[nextline] = true
337		end
338	end
339
340	assert(io.close(fh))
341	return capentries
342end
343
344local function process_compat()
345	local nval = 0
346	for _, v in pairs(known_flags) do
347		if v > nval then
348			nval = v
349		end
350	end
351
352	nval = nval << 1
353	for _, v in pairs(compat_options) do
354		if v.stdcompat ~= nil then
355			local stdcompat = v.stdcompat
356			v.definition = "COMPAT_" .. stdcompat:upper()
357			v.compatlevel = tonumber(stdcompat:match("([0-9]+)$"))
358			v.flag = stdcompat:gsub("FREEBSD", "COMPAT")
359			v.prefix = stdcompat:lower() .. "_"
360			v.descr = stdcompat:lower()
361		end
362
363		local tmpname = "sys" .. v.flag:lower()
364		local dcltmpname = tmpname .. "dcl"
365		files[tmpname] = io.tmpfile()
366		files[dcltmpname] = io.tmpfile()
367		v.tmp = tmpname
368		v.dcltmp = dcltmpname
369
370		known_flags[v.flag] = nval
371		v.mask = nval
372		nval = nval << 1
373
374		v.count = 0
375	end
376end
377
378local function process_abi_flags()
379	local flags, mask = config.abi_flags, 0
380	for txtflag in flags:gmatch("([^|]+)") do
381		if known_abi_flags[txtflag] == nil then
382			abort(1, "Unknown abi_flag: " .. txtflag)
383		end
384
385		mask = mask | known_abi_flags[txtflag].value
386	end
387
388	config.abi_flags_mask = mask
389end
390
391local function process_obsol()
392	local obsol = config.obsol
393	for syscall in obsol:gmatch("([^ ]+)") do
394		config.obsol_dict[syscall] = true
395	end
396end
397
398local function process_unimpl()
399	local unimpl = config.unimpl
400	for syscall in unimpl:gmatch("([^ ]+)") do
401		config.unimpl_dict[syscall] = true
402	end
403end
404
405local function process_syscall_abi_change()
406	local changes_abi = config.syscall_abi_change
407	for syscall in changes_abi:gmatch("([^ ]+)") do
408		config.sys_abi_change[syscall] = true
409	end
410
411	local no_changes = config.syscall_no_abi_change
412	for syscall in no_changes:gmatch("([^ ]+)") do
413		config.sys_no_abi_change[syscall] = true
414	end
415end
416
417local function abi_changes(name)
418	if known_abi_flags[name] == nil then
419		abort(1, "abi_changes: unknown flag: " .. name)
420	end
421
422	return config.abi_flags_mask & known_abi_flags[name].value ~= 0
423end
424
425local function strip_abi_prefix(funcname)
426	local abiprefix = config.abi_func_prefix
427	local stripped_name
428	if funcname == nil then
429		return nil
430	end
431	if abiprefix ~= "" and funcname:find("^" .. abiprefix) then
432		stripped_name = funcname:gsub("^" .. abiprefix, "")
433	else
434		stripped_name = funcname
435	end
436
437	return stripped_name
438end
439
440local function read_file(tmpfile)
441	if files[tmpfile] == nil then
442		print("Not found: " .. tmpfile)
443		return
444	end
445
446	local fh = files[tmpfile]
447	assert(fh:seek("set"))
448	return assert(fh:read("a"))
449end
450
451local function write_line(tmpfile, line)
452	if files[tmpfile] == nil then
453		print("Not found: " .. tmpfile)
454		return
455	end
456	assert(files[tmpfile]:write(line))
457end
458
459local function write_line_pfile(tmppat, line)
460	for k in pairs(files) do
461		if k:match(tmppat) ~= nil then
462			assert(files[k]:write(line))
463		end
464	end
465end
466
467-- Check both literal intptr_t and the abi version because this needs
468-- to work both before and after the substitution
469local function isptrtype(type)
470	return type:find("*") or type:find("caddr_t") or
471	    type:find("intptr_t") or type:find(config.abi_intptr_t)
472end
473
474local function isptrarraytype(type)
475	return type:find("[*][*]") or type:find("[*][ ]*const[ ]*[*]")
476end
477
478-- Find types that are always 64-bits wide
479local function is64bittype(type)
480	return type:find("^dev_t[ ]*$") or type:find("^id_t[ ]*$") or type:find("^off_t[ ]*$")
481end
482
483local process_syscall_def
484
485-- These patterns are processed in order on any line that isn't empty.
486local pattern_table = {
487	{
488		-- To be removed soon
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		local sys_prefix = "sys_"
870		if funcname == "nosys" or funcname == "lkmnosys" or
871		    funcname == "sysarch" or funcname:find("^freebsd") or
872		    funcname:find("^linux") then
873			sys_prefix = ""
874		end
875		write_line("sysdcl", string.format(
876		    "%s\t%s%s(struct thread *, struct %s *);\n",
877		    rettype, sys_prefix, funcname, argalias))
878		write_line("sysaue", string.format("#define\t%sAUE_%s\t%s\n",
879		    config.syscallprefix, funcalias, auditev))
880	end
881
882	write_line("sysent",
883	    string.format("\t{ .sy_narg = %s, .sy_call = (sy_call_t *)", argssize))
884	local column = 8 + 2 + #argssize + 15
885
886	if flags & known_flags.SYSMUX ~= 0 then
887		write_line("sysent", string.format(
888		    "nosys, .sy_auevent = AUE_NULL, " ..
889		    ".sy_flags = %s, .sy_thrcnt = SY_THR_STATIC },",
890		    sysflags))
891		column = column + #"nosys" + #"AUE_NULL" + 3
892	elseif flags & known_flags.NOSTD ~= 0 then
893		write_line("sysent", string.format(
894		    "lkmressys, .sy_auevent = AUE_NULL, " ..
895		    ".sy_flags = %s, .sy_thrcnt = SY_THR_ABSENT },",
896		    sysflags))
897		column = column + #"lkmressys" + #"AUE_NULL" + 3
898	else
899		if funcname == "nosys" or funcname == "lkmnosys" or
900		    funcname == "sysarch" or funcname:find("^freebsd") or
901		    funcname:find("^linux") then
902			write_line("sysent", string.format(
903			    "%s, .sy_auevent = %s, .sy_flags = %s, .sy_thrcnt = %s },",
904			    funcname, auditev, sysflags, thr_flag))
905			column = column + #funcname + #auditev + #sysflags + 3
906		else
907			write_line("sysent", string.format(
908			    "sys_%s, .sy_auevent = %s, .sy_flags = %s, .sy_thrcnt = %s },",
909			    funcname, auditev, sysflags, thr_flag))
910			column = column + #funcname + #auditev + #sysflags + 7
911		end
912	end
913
914	align_sysent_comment(column)
915	write_line("sysent", string.format("/* %d = %s */\n",
916	    sysnum, funcalias))
917	write_line("sysnames", string.format("\t\"%s\",\t\t\t/* %d = %s */\n",
918	    funcalias, sysnum, funcalias))
919
920	if flags & known_flags.NODEF == 0 then
921		write_line("syshdr", string.format("#define\t%s%s\t%d\n",
922		    config.syscallprefix, funcalias, sysnum))
923		write_line("sysmk", string.format(" \\\n\t%s.o",
924		    funcalias))
925	end
926end
927
928local function handle_obsol(sysnum, funcname, comment)
929	write_line("sysent",
930	    "\t{ .sy_narg = 0, .sy_call = (sy_call_t *)nosys, " ..
931	    ".sy_auevent = AUE_NULL, .sy_flags = 0, .sy_thrcnt = SY_THR_ABSENT },")
932	align_sysent_comment(34)
933
934	write_line("sysent", string.format("/* %d = obsolete %s */\n",
935	    sysnum, comment))
936	write_line("sysnames", string.format(
937	    "\t\"obs_%s\",\t\t\t/* %d = obsolete %s */\n",
938	    funcname, sysnum, comment))
939	write_line("syshdr", string.format("\t\t\t\t/* %d is obsolete %s */\n",
940	    sysnum, comment))
941end
942
943local function handle_compat(sysnum, thr_flag, flags, sysflags, rettype,
944    auditev, funcname, funcalias, funcargs, argalias)
945	local argssize, out, outdcl, wrap, prefix, descr
946
947	if #funcargs > 0 or flags & known_flags.NODEF ~= 0 then
948		argssize = "AS(" .. argalias .. ")"
949	else
950		argssize = "0"
951	end
952
953	for _, v in pairs(compat_options) do
954		if flags & v.mask ~= 0 then
955			if config.mincompat > v.compatlevel then
956				funcname = strip_abi_prefix(funcname)
957				funcname = v.prefix .. funcname
958				return handle_obsol(sysnum, funcname, funcname)
959			end
960			v.count = v.count + 1
961			out = v.tmp
962			outdcl = v.dcltmp
963			wrap = v.flag:lower()
964			prefix = v.prefix
965			descr = v.descr
966			goto compatdone
967		end
968	end
969
970	::compatdone::
971	local dprotoflags = get_mask({"NOPROTO", "NODEF"})
972	local nargflags = dprotoflags | known_flags.NOARGS
973	if #funcargs > 0 and flags & nargflags == 0 then
974		write_line(out, string.format("struct %s {\n", argalias))
975		for _, v in ipairs(funcargs) do
976			local argname, argtype = v.name, v.type
977			write_line(out, string.format(
978			    "\tchar %s_l_[PADL_(%s)]; %s %s; char %s_r_[PADR_(%s)];\n",
979			    argname, argtype,
980			    argtype, argname,
981			    argname, argtype))
982		end
983		write_line(out, "};\n")
984	elseif flags & nargflags == 0 then
985		write_line("sysarg", string.format(
986		    "struct %s {\n\tsyscallarg_t dummy;\n};\n", argalias))
987	end
988	if flags & dprotoflags == 0 then
989		write_line(outdcl, string.format(
990		    "%s\t%s%s(struct thread *, struct %s *);\n",
991		    rettype, prefix, funcname, argalias))
992		write_line("sysaue", string.format(
993		    "#define\t%sAUE_%s%s\t%s\n", config.syscallprefix,
994		    prefix, funcname, auditev))
995	end
996
997	if flags & known_flags.NOSTD ~= 0 then
998		write_line("sysent", string.format(
999		    "\t{ .sy_narg = %s, .sy_call = (sy_call_t *)%s, " ..
1000		    ".sy_auevent = %s, .sy_flags = 0, " ..
1001		    ".sy_thrcnt = SY_THR_ABSENT },",
1002		    "0", "lkmressys", "AUE_NULL"))
1003		align_sysent_comment(8 + 2 + #"0" + 15 + #"lkmressys" +
1004		    #"AUE_NULL" + 3)
1005	else
1006		write_line("sysent", string.format(
1007		    "\t{ %s(%s,%s), .sy_auevent = %s, .sy_flags = %s, .sy_thrcnt = %s },",
1008		    wrap, argssize, funcname, auditev, sysflags, thr_flag))
1009		align_sysent_comment(8 + 9 + #argssize + 1 + #funcname +
1010		    #auditev + #sysflags + 4)
1011	end
1012
1013	write_line("sysent", string.format("/* %d = %s %s */\n",
1014	    sysnum, descr, funcalias))
1015	write_line("sysnames", string.format(
1016	    "\t\"%s.%s\",\t\t/* %d = %s %s */\n",
1017	    wrap, funcalias, sysnum, descr, funcalias))
1018	-- Do not provide freebsdN_* symbols in libc for < FreeBSD 7
1019	local nosymflags = get_mask({"COMPAT", "COMPAT4", "COMPAT6"})
1020	if flags & nosymflags ~= 0 then
1021		write_line("syshdr", string.format(
1022		    "\t\t\t\t/* %d is %s %s */\n",
1023		    sysnum, descr, funcalias))
1024	elseif flags & known_flags.NODEF == 0 then
1025		write_line("syshdr", string.format("#define\t%s%s%s\t%d\n",
1026		    config.syscallprefix, prefix, funcalias, sysnum))
1027		write_line("sysmk", string.format(" \\\n\t%s%s.o",
1028		    prefix, funcalias))
1029	end
1030end
1031
1032local function handle_unimpl(sysnum, sysstart, sysend, comment)
1033	if sysstart == nil and sysend == nil then
1034		sysstart = tonumber(sysnum)
1035		sysend = tonumber(sysnum)
1036	end
1037
1038	sysnum = sysstart
1039	while sysnum <= sysend do
1040		write_line("sysent", string.format(
1041		    "\t{ .sy_narg = 0, .sy_call = (sy_call_t *)nosys, " ..
1042		    ".sy_auevent = AUE_NULL, .sy_flags = 0, " ..
1043		    ".sy_thrcnt = SY_THR_ABSENT },\t\t\t/* %d = %s */\n",
1044		    sysnum, comment))
1045		write_line("sysnames", string.format(
1046		    "\t\"#%d\",\t\t\t/* %d = %s */\n",
1047		    sysnum, sysnum, comment))
1048		sysnum = sysnum + 1
1049	end
1050end
1051
1052local function handle_reserved(sysnum, sysstart, sysend)
1053	handle_unimpl(sysnum, sysstart, sysend, "reserved for local use")
1054end
1055
1056process_syscall_def = function(line)
1057	local sysstart, sysend, flags, funcname, sysflags
1058	local thr_flag, syscallret
1059	local orig = line
1060	flags = 0
1061	thr_flag = "SY_THR_STATIC"
1062
1063	-- Parse out the interesting information first
1064	local initialExpr = "^([^%s]+)%s+([^%s]+)%s+([^%s]+)%s*"
1065	local sysnum, auditev, allflags = line:match(initialExpr)
1066
1067	if sysnum == nil or auditev == nil or allflags == nil then
1068		-- XXX TODO: Better?
1069		abort(1, "Completely malformed: " .. line)
1070	end
1071
1072	if sysnum:find("-") then
1073		sysstart, sysend = sysnum:match("^([%d]+)-([%d]+)$")
1074		if sysstart == nil or sysend == nil then
1075			abort(1, "Malformed range: " .. sysnum)
1076		end
1077		sysnum = nil
1078		sysstart = tonumber(sysstart)
1079		sysend = tonumber(sysend)
1080		if sysstart ~= maxsyscall + 1 then
1081			abort(1, "syscall number out of sync, missing " ..
1082			    maxsyscall + 1)
1083		end
1084	else
1085		sysnum = tonumber(sysnum)
1086		if sysnum ~= maxsyscall + 1 then
1087			abort(1, "syscall number out of sync, missing " ..
1088			    maxsyscall + 1)
1089		end
1090	end
1091
1092	-- Split flags
1093	for flag in allflags:gmatch("([^|]+)") do
1094		if known_flags[flag] == nil then
1095			abort(1, "Unknown flag " .. flag .. " for " ..  sysnum)
1096		end
1097		flags = flags | known_flags[flag]
1098	end
1099
1100	if (flags & get_mask({"RESERVED", "UNIMPL"})) == 0 and sysnum == nil then
1101		abort(1, "Range only allowed with RESERVED and UNIMPL: " .. line)
1102	end
1103
1104	if (flags & known_flags.NOTSTATIC) ~= 0 then
1105		thr_flag = "SY_THR_ABSENT"
1106	end
1107
1108	-- Strip earlier bits out, leave declaration + alt
1109	line = line:gsub("^.+" .. allflags .. "%s*", "")
1110
1111	local decl_fnd = line:find("^{") ~= nil
1112	if decl_fnd and line:find("}") == nil then
1113		abort(1, "Malformed, no closing brace: " .. line)
1114	end
1115
1116	local decl, alt
1117	if decl_fnd then
1118		line = line:gsub("^{", "")
1119		decl, alt = line:match("([^}]*)}[%s]*(.*)$")
1120	else
1121		alt = line
1122	end
1123
1124	if decl == nil and alt == nil then
1125		abort(1, "Malformed bits: " .. line)
1126	end
1127
1128	local funcalias, funcomment, argalias, rettype, args
1129	if not decl_fnd and alt ~= nil and alt ~= "" then
1130		-- Peel off one entry for name
1131		funcname = trim(alt:match("^([^%s]+)"), nil)
1132		alt = alt:gsub("^([^%s]+)[%s]*", "")
1133	end
1134	-- Do we even need it?
1135	if flags & get_mask({"OBSOL", "UNIMPL"}) ~= 0 then
1136		local NF = 0
1137		for _ in orig:gmatch("[^%s]+") do
1138			NF = NF + 1
1139		end
1140
1141		funcomment = funcname or ''
1142		if NF < 6 then
1143			funcomment = funcomment .. " " .. alt
1144		end
1145
1146		funcomment = trim(funcomment)
1147
1148--		if funcname ~= nil then
1149--		else
1150--			funcomment = trim(alt)
1151--		end
1152		goto skipalt
1153	end
1154
1155	if alt ~= nil and alt ~= "" then
1156		local altExpr = "^([^%s]+)%s+([^%s]+)%s+([^%s]+)"
1157		funcalias, argalias, rettype = alt:match(altExpr)
1158		funcalias = trim(funcalias)
1159		if funcalias == nil or argalias == nil or rettype == nil then
1160			abort(1, "Malformed alt: " .. line)
1161		end
1162	end
1163	if decl_fnd then
1164		-- Don't clobber rettype set in the alt information
1165		if rettype == nil then
1166			rettype = "int"
1167		end
1168		-- Peel off the return type
1169		syscallret = line:match("([^%s]+)%s")
1170		line = line:match("[^%s]+%s(.+)")
1171		-- Pointer incoming
1172		if line:sub(1,1) == "*" then
1173			syscallret = syscallret .. " "
1174		end
1175		while line:sub(1,1) == "*" do
1176			line = line:sub(2)
1177			syscallret = syscallret .. "*"
1178		end
1179		funcname = line:match("^([^(]+)%(")
1180		if funcname == nil then
1181			abort(1, "Not a signature? " .. line)
1182		end
1183		args = line:match("^[^(]+%((.+)%)[^)]*$")
1184		args = trim(args, '[,%s]')
1185	end
1186
1187	::skipalt::
1188
1189	if funcname == nil then
1190		funcname = funcalias
1191	end
1192
1193	funcname = trim(funcname)
1194
1195	if config.obsol_dict[funcname] then
1196		local compat_prefix = ""
1197		for _, v in pairs(compat_options) do
1198			if flags & v.mask ~= 0 then
1199				compat_prefix = v.prefix
1200				goto obsol_compat_done
1201			end
1202		end
1203		::obsol_compat_done::
1204		args = nil
1205		flags = known_flags.OBSOL
1206		funcomment = compat_prefix .. funcname
1207	end
1208	if config.unimpl_dict[funcname] then
1209		flags = known_flags.UNIMPL
1210		funcomment = funcname
1211	end
1212
1213	sysflags = "0"
1214
1215	-- NODEF events do not get audited
1216	if flags & known_flags.NODEF ~= 0 then
1217		auditev = 'AUE_NULL'
1218	end
1219
1220	-- If applicable; strip the ABI prefix from the name
1221	local stripped_name = strip_abi_prefix(funcname)
1222
1223	if flags & known_flags.CAPENABLED ~= 0 or
1224	    config.capenabled[funcname] ~= nil or
1225	    config.capenabled[stripped_name] ~= nil then
1226		sysflags = "SYF_CAPENABLED"
1227	end
1228
1229	local funcargs = {}
1230	local changes_abi = false
1231	if args ~= nil then
1232		funcargs, changes_abi = process_args(args)
1233	end
1234	if config.sys_no_abi_change[funcname] then
1235		changes_abi = false
1236	end
1237	local noproto = config.abi_flags ~= "" and not changes_abi
1238
1239	local argprefix = ''
1240	local funcprefix = ''
1241	if abi_changes("pointer_args") then
1242		for _, v in ipairs(funcargs) do
1243			if isptrtype(v.type) then
1244				if config.sys_no_abi_change[funcname] then
1245					print("WARNING: " .. funcname ..
1246					    " in syscall_no_abi_change, but pointers args are present")
1247				end
1248				changes_abi = true
1249				goto ptrfound
1250			end
1251		end
1252		::ptrfound::
1253	end
1254	if config.sys_abi_change[funcname] then
1255		changes_abi = true
1256	end
1257	if changes_abi then
1258		-- argalias should be:
1259		--   COMPAT_PREFIX + ABI Prefix + funcname
1260		argprefix = config.abi_func_prefix
1261		funcprefix = config.abi_func_prefix
1262		funcalias = funcprefix .. funcname
1263		noproto = false
1264	end
1265	if funcname ~= nil then
1266		funcname = funcprefix .. funcname
1267	end
1268	if funcalias == nil or funcalias == "" then
1269		funcalias = funcname
1270	end
1271
1272	if argalias == nil and funcname ~= nil then
1273		argalias = funcname .. "_args"
1274		for _, v in pairs(compat_options) do
1275			local mask = v.mask
1276			if (flags & mask) ~= 0 then
1277				-- Multiple aliases doesn't seem to make
1278				-- sense.
1279				argalias = v.prefix .. argalias
1280				goto out
1281			end
1282		end
1283		::out::
1284	elseif argalias ~= nil then
1285		argalias = argprefix .. argalias
1286	end
1287
1288	local ncompatflags = get_mask({"STD", "NODEF", "NOARGS", "NOPROTO",
1289	    "NOSTD"})
1290	local compatflags = get_mask_pat("COMPAT.*")
1291	if noproto or flags & known_flags.SYSMUX ~= 0 then
1292		flags = flags | known_flags.NOPROTO;
1293	end
1294	if flags & known_flags.OBSOL ~= 0 then
1295		handle_obsol(sysnum, funcname, funcomment)
1296	elseif flags & known_flags.RESERVED ~= 0 then
1297		handle_reserved(sysnum, sysstart, sysend)
1298	elseif flags & known_flags.UNIMPL ~= 0 then
1299		handle_unimpl(sysnum, sysstart, sysend, funcomment)
1300	elseif flags & compatflags ~= 0 then
1301		if flags & known_flags.STD ~= 0 then
1302			abort(1, "Incompatible COMPAT/STD: " .. line)
1303		end
1304		handle_compat(sysnum, thr_flag, flags, sysflags, rettype,
1305		    auditev, funcname, funcalias, funcargs, argalias)
1306	elseif flags & ncompatflags ~= 0 then
1307		handle_noncompat(sysnum, thr_flag, flags, sysflags, rettype,
1308		    auditev, syscallret, funcname, funcalias, funcargs,
1309		    argalias)
1310	else
1311		abort(1, "Bad flags? " .. line)
1312	end
1313
1314	if sysend ~= nil then
1315		maxsyscall = sysend
1316	elseif sysnum ~= nil then
1317		maxsyscall = sysnum
1318	end
1319end
1320
1321-- Entry point
1322
1323if #arg < 1 or #arg > 2 then
1324	error("usage: " .. arg[0] .. " input-file <config-file>")
1325end
1326
1327local sysfile, configfile = arg[1], arg[2]
1328
1329-- process_config either returns nil and a message, or a
1330-- table that we should merge into the global config
1331if configfile ~= nil then
1332	local res = assert(process_config(configfile))
1333
1334	for k, v in pairs(res) do
1335		if v ~= config[k] then
1336			config[k] = v
1337			config_modified[k] = true
1338		end
1339	end
1340end
1341
1342local compat_set = config.compat_set
1343if compat_set ~= "" then
1344	if not compat_option_sets[compat_set] then
1345		abort(1, "Undefined compat set: " .. compat_set)
1346	end
1347
1348	compat_options = compat_option_sets[compat_set]
1349else
1350	compat_options = {}
1351end
1352
1353-- We ignore errors here if we're relying on the default configuration.
1354if not config_modified.capenabled then
1355	config.capenabled = grab_capenabled(config.capabilities_conf,
1356	    config_modified.capabilities_conf == nil)
1357elseif config.capenabled ~= "" then
1358	-- Due to limitations in the config format mostly, we'll have a comma
1359	-- separated list.  Parse it into lines
1360	local capenabled = {}
1361	-- print("here: " .. config.capenabled)
1362	for sysc in config.capenabled:gmatch("([^,]+)") do
1363		capenabled[sysc] = true
1364	end
1365	config.capenabled = capenabled
1366end
1367process_compat()
1368process_abi_flags()
1369process_syscall_abi_change()
1370process_obsol()
1371process_unimpl()
1372
1373if not lfs.mkdir(tmpspace) then
1374	error("Failed to create tempdir " .. tmpspace)
1375end
1376
1377-- XXX Revisit the error handling here, we should probably move the rest of this
1378-- into a function that we pcall() so we can catch the errors and clean up
1379-- gracefully.
1380for _, v in ipairs(temp_files) do
1381	local tmpname = tmpspace .. v
1382	files[v] = io.open(tmpname, "w+")
1383	-- XXX Revisit these with a pcall() + error handler
1384	if not files[v] then
1385		abort(1, "Failed to open temp file: " .. tmpname)
1386	end
1387end
1388
1389for _, v in ipairs(output_files) do
1390	local tmpname = tmpspace .. v
1391	files[v] = io.open(tmpname, "w+")
1392	-- XXX Revisit these with a pcall() + error handler
1393	if not files[v] then
1394		abort(1, "Failed to open temp output file: " .. tmpname)
1395	end
1396end
1397
1398-- Write out all of the preamble bits
1399write_line("sysent", string.format([[
1400
1401/* The casts are bogus but will do for now. */
1402struct sysent %s[] = {
1403]], config.switchname))
1404
1405write_line("syssw", string.format([[/*
1406 * System call switch table.
1407 *
1408 * DO NOT EDIT-- this file is automatically %s.
1409 */
1410
1411]], generated_tag))
1412
1413write_line("sysarg", string.format([[/*
1414 * System call prototypes.
1415 *
1416 * DO NOT EDIT-- this file is automatically %s.
1417 */
1418
1419#ifndef %s
1420#define	%s
1421
1422#include <sys/signal.h>
1423#include <sys/acl.h>
1424#include <sys/cpuset.h>
1425#include <sys/domainset.h>
1426#include <sys/_ffcounter.h>
1427#include <sys/_semaphore.h>
1428#include <sys/ucontext.h>
1429#include <sys/wait.h>
1430
1431#include <bsm/audit_kevents.h>
1432
1433struct proc;
1434
1435struct thread;
1436
1437#define	PAD_(t)	(sizeof(syscallarg_t) <= sizeof(t) ? \
1438		0 : sizeof(syscallarg_t) - sizeof(t))
1439
1440#if BYTE_ORDER == LITTLE_ENDIAN
1441#define	PADL_(t)	0
1442#define	PADR_(t)	PAD_(t)
1443#else
1444#define	PADL_(t)	PAD_(t)
1445#define	PADR_(t)	0
1446#endif
1447
1448]], generated_tag, config.sysproto_h, config.sysproto_h))
1449if abi_changes("pair_64bit") then
1450	write_line("sysarg", string.format([[
1451#if !defined(PAD64_REQUIRED) && !defined(__amd64__)
1452#define PAD64_REQUIRED
1453#endif
1454]]))
1455end
1456if abi_changes("pair_64bit") then
1457	write_line("systrace", string.format([[
1458#if !defined(PAD64_REQUIRED) && !defined(__amd64__)
1459#define PAD64_REQUIRED
1460#endif
1461]]))
1462end
1463for _, v in pairs(compat_options) do
1464	write_line(v.tmp, string.format("\n#ifdef %s\n\n", v.definition))
1465end
1466
1467write_line("sysnames", string.format([[/*
1468 * System call names.
1469 *
1470 * DO NOT EDIT-- this file is automatically %s.
1471 */
1472
1473const char *%s[] = {
1474]], generated_tag, config.namesname))
1475
1476write_line("syshdr", string.format([[/*
1477 * System call numbers.
1478 *
1479 * DO NOT EDIT-- this file is automatically %s.
1480 */
1481
1482]], generated_tag))
1483
1484write_line("sysmk", string.format([[# FreeBSD system call object files.
1485# DO NOT EDIT-- this file is automatically %s.
1486MIASM = ]], generated_tag))
1487
1488write_line("systrace", string.format([[/*
1489 * System call argument to DTrace register array converstion.
1490 *
1491 * DO NOT EDIT-- this file is automatically %s.
1492 * This file is part of the DTrace syscall provider.
1493 */
1494
1495static void
1496systrace_args(int sysnum, void *params, uint64_t *uarg, int *n_args)
1497{
1498	int64_t *iarg = (int64_t *)uarg;
1499	int a = 0;
1500	switch (sysnum) {
1501]], generated_tag))
1502
1503write_line("systracetmp", [[static void
1504systrace_entry_setargdesc(int sysnum, int ndx, char *desc, size_t descsz)
1505{
1506	const char *p = NULL;
1507	switch (sysnum) {
1508]])
1509
1510write_line("systraceret", [[static void
1511systrace_return_setargdesc(int sysnum, int ndx, char *desc, size_t descsz)
1512{
1513	const char *p = NULL;
1514	switch (sysnum) {
1515]])
1516
1517-- Processing the sysfile will parse out the preprocessor bits and put them into
1518-- the appropriate place.  Any syscall-looking lines get thrown into the sysfile
1519-- buffer, one per line, for later processing once they're all glued together.
1520process_sysfile(sysfile)
1521
1522write_line("sysinc",
1523    "\n#define AS(name) (sizeof(struct name) / sizeof(syscallarg_t))\n")
1524
1525for _, v in pairs(compat_options) do
1526	if v.count > 0 then
1527		write_line("sysinc", string.format([[
1528
1529#ifdef %s
1530#define %s(n, name) .sy_narg = n, .sy_call = (sy_call_t *)__CONCAT(%s, name)
1531#else
1532#define %s(n, name) .sy_narg = 0, .sy_call = (sy_call_t *)nosys
1533#endif
1534]], v.definition, v.flag:lower(), v.prefix, v.flag:lower()))
1535	end
1536
1537	write_line(v.dcltmp, string.format("\n#endif /* %s */\n\n",
1538	    v.definition))
1539end
1540
1541write_line("sysprotoend", string.format([[
1542
1543#undef PAD_
1544#undef PADL_
1545#undef PADR_
1546
1547#endif /* !%s */
1548]], config.sysproto_h))
1549
1550write_line("sysmk", "\n")
1551write_line("sysent", "};\n")
1552write_line("sysnames", "};\n")
1553-- maxsyscall is the highest seen; MAXSYSCALL should be one higher
1554write_line("syshdr", string.format("#define\t%sMAXSYSCALL\t%d\n",
1555    config.syscallprefix, maxsyscall + 1))
1556write_line("systrace", [[
1557	default:
1558		*n_args = 0;
1559		break;
1560	};
1561}
1562]])
1563
1564write_line("systracetmp", [[
1565	default:
1566		break;
1567	};
1568	if (p != NULL)
1569		strlcpy(desc, p, descsz);
1570}
1571]])
1572
1573write_line("systraceret", [[
1574	default:
1575		break;
1576	};
1577	if (p != NULL)
1578		strlcpy(desc, p, descsz);
1579}
1580]])
1581
1582-- Finish up; output
1583write_line("syssw", read_file("sysinc"))
1584write_line("syssw", read_file("sysent"))
1585
1586write_line("sysproto", read_file("sysarg"))
1587write_line("sysproto", read_file("sysdcl"))
1588for _, v in pairs(compat_options) do
1589	write_line("sysproto", read_file(v.tmp))
1590	write_line("sysproto", read_file(v.dcltmp))
1591end
1592write_line("sysproto", read_file("sysaue"))
1593write_line("sysproto", read_file("sysprotoend"))
1594
1595write_line("systrace", read_file("systracetmp"))
1596write_line("systrace", read_file("systraceret"))
1597
1598for _, v in ipairs(output_files) do
1599	local target = config[v]
1600	if target ~= "/dev/null" then
1601		local fh = assert(io.open(target, "w+"))
1602		if fh == nil then
1603			abort(1, "Failed to open '" .. target .. "'")
1604		end
1605		assert(fh:write(read_file(v)))
1606		assert(fh:close())
1607	end
1608end
1609
1610cleanup()
1611