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