chiark / gitweb /
src/method-{proto,impl}.lisp: Abolish `sod-message-no-varargs-tail'.
[sod] / src / c-types-parse.lisp
CommitLineData
dea4d055
MW
1;;; -*-lisp-*-
2;;;
3;;; Parser for C types
4;;;
5;;; (c) 2009 Straylight/Edgeware
6;;;
7
8;;;----- Licensing notice ---------------------------------------------------
9;;;
e0808c47 10;;; This file is part of the Sensible Object Design, an object system for C.
dea4d055
MW
11;;;
12;;; SOD is free software; you can redistribute it and/or modify
13;;; it under the terms of the GNU General Public License as published by
14;;; the Free Software Foundation; either version 2 of the License, or
15;;; (at your option) any later version.
16;;;
17;;; SOD is distributed in the hope that it will be useful,
18;;; but WITHOUT ANY WARRANTY; without even the implied warranty of
19;;; MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
20;;; GNU General Public License for more details.
21;;;
22;;; You should have received a copy of the GNU General Public License
23;;; along with SOD; if not, write to the Free Software Foundation,
24;;; Inc., 59 Temple Place - Suite 330, Boston, MA 02111-1307, USA.
25
26(cl:in-package #:sod)
27
28;;;--------------------------------------------------------------------------
29;;; Declaration specifiers.
bf090e02
MW
30;;;
31;;; This stuff is distressingly complicated.
32;;;
33;;; Parsing a (single) declaration specifier is quite easy, and a declaration
34;;; is just a sequence of these things. Except that there are a stack of
35;;; rules about which ones are allowed to go together, and the language
36;;; doesn't require them to appear in any particular order.
37;;;
38;;; A collection of declaration specifiers is carried about in a purpose-made
39;;; object with a number of handy operations defined on it, and then I build
40;;; some parsers in terms of them. The basic strategy is to parse
41;;; declaration specifiers while they're valid, and keep track of what we've
42;;; read. When I've reached the end, we'll convert what we've got into a
43;;; `canonical form', and then convert that into a C type object of the
44;;; appropriate kind. The whole business is rather more complicated than it
45;;; really ought to be.
46
47;; Firstly, a table of interesting things about the various declaration
48;; specifiers that I might encounter. I categorize declaration specifiers
49;; into four kinds.
50;;
51;; * `Type specifiers' describe the actual type, whether that's integer,
52;; character, floating point, or some tagged or user-named type.
53;;
54;; * `Size specifiers' distinguish different sizes of the same basic type.
55;; This is how we tell the difference between `int' and `long'.
56;;
57;; * `Sign specifiers' distinguish different signednesses. This is how we
58;; tell the difference between `int' and `unsigned'.
59;;
60;; * `Qualifiers' are our old friends `const', `restrict' and `volatile'.
61;;
62;; These groupings are for my benefit here, in determining whether a
63;; particular declaration specifier is valid in the current context. I don't
64;; accept `function specifiers' (of which the only current example is
65;; `inline') since it's meaningless to me.
dea4d055
MW
66
67(defclass declspec ()
239fa5bd
MW
68 ;; Despite the fact that it looks pretty trivial, this can't be done with
69 ;; `defstruct' for the simple reason that we add more methods to the
70 ;; accessor functions later.
dea4d055
MW
71 ((label :type keyword :initarg :label :reader ds-label)
72 (name :type string :initarg :name :reader ds-name)
1645e433 73 (kind :type (member type complexity sign size qualifier)
bf090e02
MW
74 :initarg :kind :reader ds-kind)
75 (taggedp :type boolean :initarg :taggedp
76 :initform nil :reader ds-taggedp))
77 (:documentation
78 "Represents the important components of a declaration specifier.
79
80 The only interesting instances of this class are in the table
81 `*declspec-map*'."))
dea4d055
MW
82
83(defmethod shared-initialize :after ((ds declspec) slot-names &key)
bf090e02
MW
84 "If no name is provided then derive one from the label.
85
86 Most declaration specifiers have simple names for which this works well."
dea4d055
MW
87 (default-slot (ds 'name slot-names)
88 (string-downcase (ds-label ds))))
89
dea4d055
MW
90(defparameter *declspec-map*
91 (let ((map (make-hash-table :test #'equal)))
0e7cdea0
MW
92 (dolist (item '((type :void :char :int :float :double
93 (:bool :name "_Bool"))
94 (complexity (:complex :name "_Complex")
95 (:imaginary :name "_Imaginary"))
bf090e02
MW
96 ((type :taggedp t) :enum :struct :union)
97 (size :short :long (:long-long :name "long long"))
dea4d055 98 (sign :signed :unsigned)
bf090e02
MW
99 (qualifier :const :restrict :volatile)))
100 (destructuring-bind (kind &key (taggedp nil))
101 (let ((spec (car item)))
102 (if (consp spec) spec (list spec)))
dea4d055 103 (dolist (spec (cdr item))
bf090e02
MW
104 (destructuring-bind (label
105 &key
106 (name (string-downcase label))
107 (taggedp taggedp))
108 (if (consp spec) spec (list spec))
dea4d055 109 (let ((ds (make-instance 'declspec
bf090e02
MW
110 :label label
111 :name name
112 :kind kind
113 :taggedp taggedp)))
dea4d055
MW
114 (setf (gethash name map) ds
115 (gethash label map) ds))))))
0e7cdea0
MW
116 (dolist (label '(:complex :imaginary :bool))
117 (setf (gethash (string-downcase label) map) (gethash label map)))
bf090e02 118 map)
3109662a 119 "Maps symbolic labels and textual names to `declspec' instances.")
bf090e02
MW
120
121;; A collection of declaration specifiers, and how to merge them together.
122
123(defclass declspecs ()
239fa5bd
MW
124 ;; This could have been done with `defstruct' just as well, but a
125 ;; `defclass' can be tweaked interactively, which is a win at the moment.
bf090e02 126 ((type :initform nil :initarg :type :reader ds-type)
0e7cdea0 127 (complexity :initform nil :initarg :complexity :reader ds-complexity)
bf090e02
MW
128 (sign :initform nil :initarg :sign :reader ds-sign)
129 (size :initform nil :initarg :size :reader ds-size)
130 (qualifier :initform nil :initarg :qualifiers :reader ds-qualifiers))
131 (:documentation
132 "Represents a collection of declaration specifiers.
133
134 This is used during type parsing to represent the type under
135 construction. Instances are immutable: we build new ones rather than
136 modifying existing ones. This leads to a certain amount of churn, but
137 we'll just have to live with that.
138
139 (Why are instances immutable? Because it's much easier to merge a new
3109662a
MW
140 specifier into an existing collection and then check that the resulting
141 thing is valid, rather than having to deal with all of the possible
bf090e02
MW
142 special cases of what the new thing might be. And if the merged
143 collection isn't good, I must roll back to the previous version. So I
144 don't get to take advantage of a mutable structure.)"))
dea4d055
MW
145
146(defmethod ds-label ((ty c-type)) :c-type)
147(defmethod ds-name ((ty c-type)) (princ-to-string ty))
148(defmethod ds-kind ((ty c-type)) 'type)
149
150(defparameter *good-declspecs*
0e7cdea0
MW
151 '(((:int) (:signed :unsigned) (:short :long :long-long) ())
152 ((:char) (:signed :unsigned) () ())
153 ((:double) () (:long) (:complex :imaginary))
154 (t () () ()))
dea4d055
MW
155 "List of good collections of declaration specifiers.
156
0e7cdea0
MW
157 Each item is a list of the form (TYPES SIGNS SIZES COMPLEXITIES). Each of
158 TYPES, SIGNS, SIZES, and COMPLEXITIES, is either a list of acceptable
159 specifiers of the appropriate kind, or T, which matches any specifier.")
dea4d055 160
dea4d055
MW
161(defun good-declspecs-p (specs)
162 "Are SPECS a good collection of declaration specifiers?"
0e7cdea0
MW
163 (let ((speclist (list (ds-type specs)
164 (ds-sign specs)
165 (ds-size specs)
166 (ds-complexity specs))))
dea4d055
MW
167 (some (lambda (it)
168 (every (lambda (spec pat)
169 (or (eq pat t) (null spec)
170 (member (ds-label spec) pat)))
171 speclist it))
172 *good-declspecs*)))
173
174(defun combine-declspec (specs ds)
175 "Combine the declspec DS with the existing SPECS.
176
177 Returns new DECLSPECS if they're OK, or `nil' if not. The old SPECS are
178 not modified."
bf090e02 179
dea4d055
MW
180 (let* ((kind (ds-kind ds))
181 (old (slot-value specs kind)))
182 (multiple-value-bind (ok new)
183 (case kind
184 (qualifier (values t (adjoin ds old)))
185 (size (cond ((not old) (values t ds))
186 ((and (eq (ds-label old) :long) (eq ds old))
187 (values t (gethash :long-long *declspec-map*)))
188 (t (values nil nil))))
189 (t (values (not old) ds)))
190 (if ok
191 (let ((copy (copy-instance specs)))
192 (setf (slot-value copy kind) new)
193 (and (good-declspecs-p copy) copy))
194 nil))))
195
dea4d055 196(defun declspecs-type (specs)
bf090e02 197 "Convert `declspecs' SPECS into a standalone C type object."
dea4d055
MW
198 (let ((type (ds-type specs))
199 (size (ds-size specs))
bf090e02 200 (sign (ds-sign specs))
5ce911a0 201 (cplx (ds-complexity specs))
bf090e02
MW
202 (quals (mapcar #'ds-label (ds-qualifiers specs))))
203 (cond ((typep type 'c-type)
204 (qualify-c-type type quals))
5ce911a0 205 ((or type size sign cplx)
bf090e02 206 (when (and sign (eq (ds-label sign) :signed)
dea4d055
MW
207 (eq (ds-label type) :int))
208 (setf sign nil))
209 (cond ((and (or (null type) (eq (ds-label type) :int))
210 (or size sign))
211 (setf type nil))
212 ((null type)
213 (setf type (gethash :int *declspec-map*))))
214 (make-simple-type (format nil "~{~@[~A~^ ~]~}"
239fa5bd 215 (mapcar #'ds-name
dea4d055 216 (remove nil
5ce911a0
MW
217 (list sign cplx
218 size type))))
bf090e02 219 quals))
dea4d055
MW
220 (t
221 nil))))
222
bf090e02 223;; Parsing declaration specifiers.
dea4d055 224
bf090e02 225(define-indicator :declspec "<declaration-specifier>")
dea4d055 226
bf090e02
MW
227(defun scan-declspec
228 (scanner &key (predicate (constantly t)) (indicator :declspec))
3109662a 229 "Scan a `declspec' from SCANNER.
dea4d055 230
bf090e02
MW
231 If PREDICATE is provided then only succeed if (funcall PREDICATE DECLSPEC)
232 is true, where DECLSPEC is the raw declaration specifier or C-type object,
233 so we won't have fetched the tag for a tagged type yet. If the PREDICATE
234 returns false then the scan fails without consuming input.
dea4d055 235
bf090e02
MW
236 If we couldn't find an acceptable declaration specifier then issue
237 INDICATOR as the failure indicator. Value on success is either a
238 `declspec' object or a `c-type' object."
dea4d055 239
bf090e02
MW
240 ;; Turns out to be easier to do this by hand.
241 (let ((ds (and (eq (token-type scanner) :id)
242 (let ((kw (token-value scanner)))
ec5cb3ca
MW
243 (or (and (boundp '*module-type-map*)
244 (gethash kw *module-type-map*))
bf090e02
MW
245 (gethash kw *declspec-map*))))))
246 (cond ((or (not ds) (and predicate (not (funcall predicate ds))))
247 (values (list indicator) nil nil))
8293b90a 248 ((and (typep ds 'declspec) (ds-taggedp ds))
bf090e02
MW
249 (scanner-step scanner)
250 (if (eq (token-type scanner) :id)
251 (let ((ty (make-c-tagged-type (ds-label ds)
252 (token-value scanner))))
253 (scanner-step scanner)
254 (values ty t t))
255 (values :tag nil t)))
256 (t
257 (scanner-step scanner)
258 (values ds t t)))))
dea4d055 259
bf090e02
MW
260(defun scan-and-merge-declspec (scanner specs)
261 "Scan a declaration specifier and merge it with SPECS.
262
263 This is a parser function. If it succeeds, it returns the merged
264 `declspecs' object. It can fail either if no valid declaration specifier
265 is found or it cannot merge the declaration specifier with the existing
266 SPECS."
267
268 (with-parser-context (token-scanner-context :scanner scanner)
269 (if-parse (:consumedp consumedp) (scan-declspec scanner)
270 (aif (combine-declspec specs it)
271 (values it t consumedp)
272 (values (list :declspec) nil consumedp)))))
273
239fa5bd 274(export 'parse-c-type)
bf090e02
MW
275(defun parse-c-type (scanner)
276 "Parse a C type from declaration specifiers.
dea4d055 277
bf090e02
MW
278 This is a parser function. If it succeeds then the result is a `c-type'
279 object representing the type it found. Note that this function won't try
280 to parse a C declarator."
dea4d055 281
bf090e02
MW
282 (with-parser-context (token-scanner-context :scanner scanner)
283 (if-parse (:result specs :consumedp cp)
284 (many (specs (make-instance 'declspecs) it :min 1)
285 (peek (scan-and-merge-declspec scanner specs)))
286 (let ((type (declspecs-type specs)))
287 (if type (values type t cp)
288 (values (list :declspec) nil cp))))))
dea4d055 289
bf090e02
MW
290;;;--------------------------------------------------------------------------
291;;; Parsing declarators.
292;;;
293;;; The syntax of declaration specifiers was horrific. Declarators are a
294;;; very simple expression syntax, but this time the semantics are awful. In
295;;; particular, they're inside-out. If <> denotes mumble of foo, then op <>
296;;; is something like mumble of op of foo. Unfortunately, the expression
297;;; parser engine wants to apply op of mumble of foo, so I'll have to do some
298;;; work to fix the impedance mismatch.
299;;;
300;;; The currency we'll use is a pair (FUNC . NAME), with the semantics that
301;;; (funcall FUNC TYPE) returns the derived type. The result of
302;;; `parse-declarator' will be of this form.
dea4d055 303
239fa5bd 304(export 'parse-declarator)
ced609b8 305(defun parse-declarator (scanner base-type &key kernel abstractp keywordp)
239fa5bd 306 "Parse a C declarator, returning a pair (C-TYPE . NAME).
dea4d055 307
239fa5bd
MW
308 The SCANNER is a token scanner to read from. The BASE-TYPE is the type
309 extracted from the preceding declaration specifiers, as parsed by
310 `parse-c-type'.
311
312 The result contains both the resulting constructed C-TYPE (with any
313 qualifiers etc. as necessary), and the name from the middle of the
ea578bb4 314 declarator. The name is parsed using the KERNEL parser provided, and
239fa5bd
MW
315 defaults to matching a simple identifier `:id'. This might, e.g., be
316 (? :id) to parse an `abstract declarator' which has optional names.
317
ced609b8
MW
318 If KEYWORDP is true, then a keyword argument list is permitted in
319 function declarations.
320
ea578bb4 321 There's an annoying ambiguity in the syntax, if an empty KERNEL is
239fa5bd
MW
322 permitted. In this case, you must ensure that ABSTRACTP is true so that
323 the appropriate heuristic can be applied. As a convenience, if ABSTRACTP
ea578bb4 324 is true then `(? :id)' is used as the default KERNEL."
b4a2b5d9
MW
325
326 ;; This is a bit confusing. This is a strangely-shaped operator grammer,
327 ;; which wouldn't be so bad, but the `values' being operated on are pairs
328 ;; of the form (FUNC . NAME). The NAME is whatever the KERNEL parser
329 ;; produces as its result, and will be passed out unchanged. The FUNC is a
330 ;; type-constructor function which will be eventually be applied to the
331 ;; input BASE-TYPE, but we can't calculate the actual result as we go along
332 ;; because of the rather annoying inside-out nature of the declarator
333 ;; syntax.
334
239fa5bd 335 (with-parser-context (token-scanner-context :scanner scanner)
ea578bb4 336 (let ((kernel-parser (cond (kernel kernel)
239fa5bd
MW
337 (abstractp (parser () (? :id)))
338 (t (parser () :id)))))
339
340 (labels ((qualifiers ()
341 ;; qualifier*
342
343 (parse
344 (seq ((quals (list ()
345 (scan-declspec
346 scanner
347 :indicator :qualifier
348 :predicate (lambda (ds)
349 (and (typep ds 'declspec)
350 (eq (ds-kind ds)
351 'qualifier)))))))
352 (mapcar #'ds-label quals))))
353
ced609b8
MW
354 (disallow-keyword-functions (type)
355 (when (typep type 'c-keyword-function-type)
356 (error "Functions with keyword arguments are only ~
357 allowed at top-level.")))
358
239fa5bd
MW
359 (star ()
360 ;; Prefix: `*' qualifiers
361
362 (parse (seq (#\* (quals (qualifiers)))
363 (preop "*" (state 9)
364 (cons (lambda (type)
ced609b8 365 (disallow-keyword-functions type)
239fa5bd
MW
366 (funcall (car state)
367 (make-pointer-type type quals)))
368 (cdr state))))))
369
c28f6ae9
MW
370 (predict-argument-list-p ()
371 ;; See `prefix-lparen'. Predict an argument list rather
372 ;; than a nested declarator if (a) abstract declarators are
373 ;; permitted and (b) the next token is a declaration
374 ;; specifier or ellipsis.
375 (let ((type (token-type scanner))
376 (value (token-value scanner)))
377 (and abstractp
378 (or (eq type :ellipsis)
379 (and (eq type :id)
380 (or (gethash value *module-type-map*)
381 (gethash value *declspec-map*)))))))
239fa5bd
MW
382
383 (prefix-lparen ()
384 ;; Prefix: `('
385 ;;
386 ;; Opening parentheses are treated as prefix operators by
387 ;; the expression parsing engine. There's an annoying
388 ;; ambiguity in the syntax if abstract declarators are
389 ;; permitted: a `(' might be either the start of a nested
390 ;; subdeclarator or the start of a postfix function argument
391 ;; list. The two are disambiguated by stating that if the
392 ;; token following the `(' is a `)' or a declaration
393 ;; specifier, then we have a postfix argument list.
394 (parse
395 (peek (seq (#\(
c28f6ae9 396 (nil (if (predict-argument-list-p)
239fa5bd
MW
397 (values nil nil nil)
398 (values t t nil))))
399 (lparen #\))))))
400
ea578bb4
MW
401 (kernel ()
402 (parse (seq ((name (funcall kernel-parser)))
239fa5bd
MW
403 (cons #'identity name))))
404
f450a3f2
MW
405 (arg-decl (abstractp)
406 (parse (seq ((base-type (parse-c-type scanner))
407 (dtor (parse-declarator scanner base-type
408 :abstractp abstractp)))
409 dtor)))
410
411 (argument ()
412 ;; argument ::= type abstract-declspec
413
414 (parse (seq ((dtor (arg-decl t)))
415 (make-argument (cdr dtor) (car dtor)))))
416
ced609b8
MW
417 (kw-argument ()
418 ;; kw-argument ::= type declspec [= c-fragment]
419
420 (parse (seq ((dtor (arg-decl nil))
421 (dflt (? (when (eq (token-type scanner) #\=)
422 (parse-delimited-fragment
423 scanner #\= '(#\, #\))
424 :keep-end t)))))
425 (make-argument (cdr dtor) (car dtor) dflt))))
426
239fa5bd 427 (argument-list ()
f450a3f2
MW
428 ;; argument-list ::=
429 ;; [argument [`,' argument]* [`,' argument-tail]]
430 ;; | argument-tail
431 ;;
ced609b8
MW
432 ;; argument-tail ::= `...' | keyword-tail
433 ;;
434 ;; keyword-tail ::= `?' [kw-argument [`,' kw-argument]*]
435 ;;
436 ;; kw-argument ::= argument [= c-fragment]
b0ff693c
MW
437 ;;
438 ;; The possibility of a trailing `,' `...' means that we
439 ;; can't use the standard `list' parser. Note that, unlike
440 ;; `real' C, we allow an ellipsis even if there are no
441 ;; explicit arguments.
442
ced609b8
MW
443 (let ((args nil)
444 (keys nil)
445 (keysp nil))
b0ff693c
MW
446 (loop
447 (when (eq (token-type scanner) :ellipsis)
448 (push :ellipsis args)
449 (scanner-step scanner)
450 (return))
ced609b8
MW
451 (when (and keywordp (eq (token-type scanner) #\?))
452 (setf keysp t)
453 (scanner-step scanner)
454 (multiple-value-bind (arg winp consumedp)
455 (parse (list (:min 0) (kw-argument) #\,))
456 (declare (ignore consumedp))
457 (unless winp
458 (return-from argument-list (values arg nil t)))
459 (setf keys arg)
460 (return)))
b0ff693c 461 (multiple-value-bind (arg winp consumedp)
f450a3f2 462 (argument)
b0ff693c
MW
463 (unless winp
464 (if (or consumedp args)
465 (return-from argument-list (values arg nil t))
466 (return)))
467 (push arg args))
468 (unless (eq (token-type scanner) #\,)
469 (return))
470 (scanner-step scanner))
ced609b8
MW
471 (values (let ((rargs (nreverse args))
472 (rkeys (nreverse keys)))
473 (if keysp
474 (lambda (ret)
475 (make-keyword-function-type
476 ret rargs rkeys))
477 (lambda (ret)
478 (make-function-type ret rargs))))
f450a3f2 479 t
ced609b8 480 (or args keysp))))
239fa5bd
MW
481
482 (postfix-lparen ()
483 ;; Postfix: `(' argument-list `)'
484
f450a3f2 485 (parse (seq (#\( (make (argument-list)) #\))
239fa5bd
MW
486 (postop "()" (state 10)
487 (cons (lambda (type)
ced609b8 488 (disallow-keyword-functions type)
239fa5bd 489 (funcall (car state)
f450a3f2 490 (funcall make type)))
239fa5bd
MW
491 (cdr state))))))
492
493 (dimension ()
494 ;; `[' c-fragment ']'
495
496 (parse (seq ((frag (parse-delimited-fragment
497 scanner #\[ #\])))
498 (c-fragment-text frag))))
499
500 (lbracket ()
501 ;; Postfix: dimension+
502
503 (parse (seq ((dims (list (:min 1) (dimension))))
504 (postop "[]" (state 10)
505 (cons (lambda (type)
ced609b8 506 (disallow-keyword-functions type)
239fa5bd
MW
507 (funcall (car state)
508 (make-array-type type dims)))
509 (cdr state)))))))
510
511 ;; And now we actually do the declarator parsing.
512 (parse (seq ((value (expr (:nestedp nestedp)
513
514 ;; An actual operand.
ea578bb4 515 (kernel)
239fa5bd
MW
516
517 ;; Binary operators. There aren't any.
518 nil
519
520 ;; Prefix operators.
521 (or (star)
522 (prefix-lparen))
523
524 ;; Postfix operators.
525 (or (postfix-lparen)
526 (lbracket)
527 (when nestedp (seq (#\)) (rparen #\))))))))
528 (cons (funcall (car value) base-type) (cdr value))))))))
dea4d055
MW
529
530;;;----- That's all, folks --------------------------------------------------