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