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