src/c-types-{proto,impl,parse}.lisp: Add `storage specifiers' to the model.
[sod] / src / c-types-parse.lisp
1 ;;; -*-lisp-*-
2 ;;;
3 ;;; Parser for C types
4 ;;;
5 ;;; (c) 2009 Straylight/Edgeware
6 ;;;
7
8 ;;;----- Licensing notice ---------------------------------------------------
9 ;;;
10 ;;; This file is part of the Sensible Object Design, an object system for C.
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.
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.
66
67 (defclass declspec ()
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.
71 ((label :type keyword :initarg :label :reader ds-label)
72 (name :type string :initarg :name :reader ds-name)
73 (kind :type (member type complexity sign size qualifier specs)
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*'."))
82
83 (defmethod shared-initialize :after ((ds declspec) slot-names &key)
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."
87 (default-slot (ds 'name slot-names)
88 (string-downcase (ds-label ds))))
89
90 (defparameter *declspec-map*
91 (let ((map (make-hash-table :test #'equal)))
92 (dolist (item '((type :void :char :int :float :double
93 (:bool :compat "_Bool"))
94 (complexity (:complex :compat "_Complex")
95 (:imaginary :compat "_Imaginary"))
96 ((type :taggedp t) :enum :struct :union)
97 (size :short :long (:long-long :name "long long"))
98 (sign :signed :unsigned)
99 (qualifier :const :restrict :volatile
100 (:atomic :compat "_Atomic"))))
101 (destructuring-bind (kind &key (taggedp nil))
102 (let ((spec (car item)))
103 (if (consp spec) spec (list spec)))
104 (dolist (spec (cdr item))
105 (destructuring-bind (label
106 &key
107 (name (string-downcase label))
108 compat
109 (taggedp taggedp))
110 (if (consp spec) spec (list spec))
111 (let ((ds (make-instance 'declspec
112 :label label
113 :name (or compat name)
114 :kind kind
115 :taggedp taggedp)))
116 (setf (gethash name map) ds
117 (gethash label map) ds)
118 (when compat
119 (setf (gethash compat map) ds)))))))
120 map)
121 "Maps symbolic labels and textual names to `declspec' instances.")
122
123 (defclass storespec ()
124 ((spec :initarg :spec :reader ds-spec))
125 (:documentation "Carrier for a storage specifier."))
126
127 (defmethod ds-label ((spec storespec)) spec)
128 (defmethod ds-kind ((spec storespec)) 'specs)
129
130 (defmethod ds-label ((ty c-type)) :c-type)
131 (defmethod ds-name ((ty c-type)) (princ-to-string ty))
132 (defmethod ds-kind ((ty c-type)) 'type)
133
134 ;; A collection of declaration specifiers, and how to merge them together.
135
136 (defclass declspecs ()
137 ;; This could have been done with `defstruct' just as well, but a
138 ;; `defclass' can be tweaked interactively, which is a win at the moment.
139 ((type :initform nil :initarg :type :reader ds-type)
140 (complexity :initform nil :initarg :complexity :reader ds-complexity)
141 (sign :initform nil :initarg :sign :reader ds-sign)
142 (size :initform nil :initarg :size :reader ds-size)
143 (specs :initform nil :initarg :specs :reader ds-specs)
144 (qualifier :initform nil :initarg :qualifiers :reader ds-qualifiers))
145 (:documentation "Represents a collection of declaration specifiers.
146
147 This is used during type parsing to represent the type under construction.
148 Instances are immutable: we build new ones rather than modifying existing
149 ones. This leads to a certain amount of churn, but we'll just have to
150 live with that.
151
152 (Why are instances immutable? Because it's much easier to merge a new
153 specifier into an existing collection and then check that the resulting
154 thing is valid, rather than having to deal with all of the possible
155 special cases of what the new thing might be. And if the merged
156 collection isn't good, I must roll back to the previous version. So I
157 don't get to take advantage of a mutable structure.)"))
158
159 (defparameter *good-declspecs*
160 '(((:int) (:signed :unsigned) (:short :long :long-long) ())
161 ((:char) (:signed :unsigned) () ())
162 ((:double) () (:long) (:complex :imaginary))
163 (t () () ()))
164 "List of good collections of declaration specifiers.
165
166 Each item is a list of the form (TYPES SIGNS SIZES COMPLEXITIES). Each of
167 TYPES, SIGNS, SIZES, and COMPLEXITIES, is either a list of acceptable
168 specifiers of the appropriate kind, or T, which matches any specifier.")
169
170 (defun good-declspecs-p (specs)
171 "Are SPECS a good collection of declaration specifiers?"
172 (let ((speclist (list (ds-type specs)
173 (ds-sign specs)
174 (ds-size specs)
175 (ds-complexity specs))))
176 (some (lambda (it)
177 (every (lambda (spec pat)
178 (or (eq pat t) (null spec)
179 (member (ds-label spec) pat)))
180 speclist it))
181 *good-declspecs*)))
182
183 (defun combine-declspec (specs ds)
184 "Combine the declspec DS with the existing SPECS.
185
186 Returns new DECLSPECS if they're OK, or `nil' if not. The old SPECS are
187 not modified."
188
189 (let* ((kind (ds-kind ds))
190 (old (slot-value specs kind)))
191 (multiple-value-bind (ok new)
192 (case kind
193 (qualifier (values t (adjoin ds old)))
194 (size (cond ((not old) (values t ds))
195 ((and (eq (ds-label old) :long) (eq ds old))
196 (values t (gethash :long-long *declspec-map*)))
197 (t (values nil nil))))
198 (specs (values t (adjoin (ds-spec ds) old)))
199 (t (values (not old) ds)))
200 (if ok
201 (let ((copy (copy-instance specs)))
202 (setf (slot-value copy kind) new)
203 (and (good-declspecs-p copy) copy))
204 nil))))
205
206 (defun declspecs-type (specs)
207 "Convert `declspecs' SPECS into a standalone C type object."
208 (let* ((base-type (ds-type specs))
209 (size (ds-size specs))
210 (sign (ds-sign specs))
211 (cplx (ds-complexity specs))
212 (quals (mapcar #'ds-label (ds-qualifiers specs)))
213 (specs (ds-specs specs))
214 (type (cond ((typep base-type 'c-type)
215 (qualify-c-type base-type quals))
216 ((or base-type size sign cplx)
217 (when (and sign (eq (ds-label sign) :signed)
218 (eq (ds-label base-type) :int))
219 (setf sign nil))
220 (cond ((and (or (null base-type)
221 (eq (ds-label base-type) :int))
222 (or size sign))
223 (setf base-type nil))
224 ((null base-type)
225 (setf base-type (gethash :int *declspec-map*))))
226 (let* ((things (list sign cplx size base-type))
227 (stripped (remove nil things))
228 (names (mapcar #'ds-name stripped)))
229 (make-simple-type (format nil "~{~A~^ ~}" names)
230 quals)))
231 (t
232 nil))))
233 (cond ((null type) nil)
234 ((null specs) type)
235 (t (make-storage-specifiers-type type specs)))))
236
237 ;; Parsing declaration specifiers.
238
239 (define-indicator :declspec "<declaration-specifier>")
240
241 (defun scan-simple-declspec
242 (scanner &key (predicate (constantly t)) (indicator :declspec))
243 "Scan a simple `declspec' from SCANNER.
244
245 Simple declspecs are the ones defined in the `*declspec-map*' or
246 `*module-type-map*'. This covers the remaining possibilities if the
247 `complex-declspec' pluggable parser didn't find anything to match.
248
249 If PREDICATE is provided then only succeed if (funcall PREDICATE DECLSPEC)
250 is true, where DECLSPEC is the raw declaration specifier or C-type object,
251 so we won't have fetched the tag for a tagged type yet. If the PREDICATE
252 returns false then the scan fails without consuming input.
253
254 If we couldn't find an acceptable declaration specifier then issue
255 INDICATOR as the failure indicator. Value on success is either a
256 `declspec' object or a `c-type' object."
257
258 ;; Turns out to be easier to do this by hand.
259 (let ((ds (and (eq (token-type scanner) :id)
260 (let ((kw (token-value scanner)))
261 (or (and (boundp '*module-type-map*)
262 (gethash kw *module-type-map*))
263 (gethash kw *declspec-map*))))))
264 (cond ((or (not ds) (and predicate (not (funcall predicate ds))))
265 (values (list indicator) nil nil))
266 ((and (typep ds 'declspec) (ds-taggedp ds))
267 (scanner-step scanner)
268 (if (eq (token-type scanner) :id)
269 (let ((ty (make-c-tagged-type (ds-label ds)
270 (token-value scanner))))
271 (scanner-step scanner)
272 (values ty t t))
273 (values :tag nil t)))
274 (t
275 (scanner-step scanner)
276 (values ds t t)))))
277
278 (define-pluggable-parser complex-declspec atomic-typepsec (scanner)
279 ;; `atomic' `(' type-name `)'
280 ;; `_Atomic' `(' type-name `)'
281 (with-parser-context (token-scanner-context :scanner scanner)
282 (parse (peek (seq ((nil (or "atomic" "_Atomic"))
283 #\(
284 (decls (parse-c-type scanner))
285 (subtype (parse-declarator scanner decls
286 :kernel (parse-empty)
287 :abstractp t))
288 #\))
289 (make-atomic-type (car subtype)))))))
290
291 (defun scan-and-merge-declspec (scanner specs)
292 "Scan a declaration specifier and merge it with SPECS.
293
294 This is a parser function. If it succeeds, it returns the merged
295 `declspecs' object. It can fail either if no valid declaration specifier
296 is found or it cannot merge the declaration specifier with the existing
297 SPECS."
298
299 (with-parser-context (token-scanner-context :scanner scanner)
300 (if-parse (:consumedp consumedp)
301 (or (plug complex-declspec scanner)
302 (scan-simple-declspec scanner))
303 (aif (combine-declspec specs it)
304 (values it t consumedp)
305 (values (list :declspec) nil consumedp)))))
306
307 (export 'parse-c-type)
308 (defun parse-c-type (scanner)
309 "Parse a C type from declaration specifiers.
310
311 This is a parser function. If it succeeds then the result is a `c-type'
312 object representing the type it found. Note that this function won't try
313 to parse a C declarator."
314
315 (with-parser-context (token-scanner-context :scanner scanner)
316 (if-parse (:result specs :consumedp cp)
317 (many (specs (make-instance 'declspecs) it :min 1)
318 (peek (scan-and-merge-declspec scanner specs)))
319 (let ((type (declspecs-type specs)))
320 (if type (values type t cp)
321 (values (list :declspec) nil cp))))))
322
323 ;;;--------------------------------------------------------------------------
324 ;;; Parsing declarators.
325 ;;;
326 ;;; The syntax of declaration specifiers was horrific. Declarators are a
327 ;;; very simple expression syntax, but this time the semantics are awful. In
328 ;;; particular, they're inside-out. If <> denotes mumble of foo, then op <>
329 ;;; is something like mumble of op of foo. Unfortunately, the expression
330 ;;; parser engine wants to apply op of mumble of foo, so I'll have to do some
331 ;;; work to fix the impedance mismatch.
332 ;;;
333 ;;; The currency we'll use is a pair (FUNC . NAME), with the semantics that
334 ;;; (funcall FUNC TYPE) returns the derived type. The result of
335 ;;; `parse-declarator' will be of this form.
336
337 (export 'parse-declarator)
338 (defun parse-declarator (scanner base-type &key kernel abstractp)
339 "Parse a C declarator, returning a pair (C-TYPE . NAME).
340
341 The SCANNER is a token scanner to read from. The BASE-TYPE is the type
342 extracted from the preceding declaration specifiers, as parsed by
343 `parse-c-type'.
344
345 The result contains both the resulting constructed C-TYPE (with any
346 qualifiers etc. as necessary), and the name from the middle of the
347 declarator. The name is parsed using the KERNEL parser provided, and
348 defaults to matching a simple identifier `:id'. This might, e.g., be
349 (? :id) to parse an `abstract declarator' which has optional names.
350
351 There's an annoying ambiguity in the syntax, if an empty KERNEL is
352 permitted. In this case, you must ensure that ABSTRACTP is true so that
353 the appropriate heuristic can be applied. As a convenience, if ABSTRACTP
354 is true then `(? :id)' is used as the default KERNEL."
355 (with-parser-context (token-scanner-context :scanner scanner)
356 (let ((kernel-parser (cond (kernel kernel)
357 (abstractp (parser () (? :id)))
358 (t (parser () :id)))))
359
360 (labels ((qualifiers ()
361 ;; qualifier*
362
363 (parse
364 (seq ((quals (list ()
365 (scan-simple-declspec
366 scanner
367 :indicator :qualifier
368 :predicate (lambda (ds)
369 (and (typep ds 'declspec)
370 (eq (ds-kind ds)
371 'qualifier)))))))
372 (mapcar #'ds-label quals))))
373
374 (star ()
375 ;; Prefix: `*' qualifiers
376
377 (parse (seq (#\* (quals (qualifiers)))
378 (preop "*" (state 9)
379 (cons (lambda (type)
380 (funcall (car state)
381 (make-pointer-type type quals)))
382 (cdr state))))))
383
384 (predict-argument-list-p ()
385 ;; See `prefix-lparen'. Predict an argument list rather
386 ;; than a nested declarator if (a) abstract declarators are
387 ;; permitted and (b) the next token is a declaration
388 ;; specifier or ellipsis.
389 (let ((type (token-type scanner))
390 (value (token-value scanner)))
391 (and abstractp
392 (or (eq type :ellipsis)
393 (and (eq type :id)
394 (or (gethash value *module-type-map*)
395 (gethash value *declspec-map*)))))))
396
397 (prefix-lparen ()
398 ;; Prefix: `('
399 ;;
400 ;; Opening parentheses are treated as prefix operators by
401 ;; the expression parsing engine. There's an annoying
402 ;; ambiguity in the syntax if abstract declarators are
403 ;; permitted: a `(' might be either the start of a nested
404 ;; subdeclarator or the start of a postfix function argument
405 ;; list. The two are disambiguated by stating that if the
406 ;; token following the `(' is a `)' or a declaration
407 ;; specifier, then we have a postfix argument list.
408 (parse
409 (peek (seq (#\(
410 (nil (if (predict-argument-list-p)
411 (values nil nil nil)
412 (values t t nil))))
413 (lparen #\))))))
414
415 (kernel ()
416 (parse (seq ((name (funcall kernel-parser)))
417 (cons #'identity name))))
418
419 (argument-list ()
420 ;; [argument [`,' argument]* [`,' `...']] | `...'
421 ;;
422 ;; The possibility of a trailing `,' `...' means that we
423 ;; can't use the standard `list' parser. Note that, unlike
424 ;; `real' C, we allow an ellipsis even if there are no
425 ;; explicit arguments.
426
427 (let ((args nil))
428 (loop
429 (when (eq (token-type scanner) :ellipsis)
430 (push :ellipsis args)
431 (scanner-step scanner)
432 (return))
433 (multiple-value-bind (arg winp consumedp)
434 (parse (seq ((base-type (parse-c-type scanner))
435 (dtor (parse-declarator scanner
436 base-type
437 :abstractp t)))
438 (make-argument (cdr dtor) (car dtor))))
439 (unless winp
440 (if (or consumedp args)
441 (return-from argument-list (values arg nil t))
442 (return)))
443 (push arg args))
444 (unless (eq (token-type scanner) #\,)
445 (return))
446 (scanner-step scanner))
447 (values (nreverse args) t args)))
448
449 (postfix-lparen ()
450 ;; Postfix: `(' argument-list `)'
451
452 (parse (seq (#\( (args (argument-list)) #\))
453 (postop "()" (state 10)
454 (cons (lambda (type)
455 (funcall (car state)
456 (make-function-type type args)))
457 (cdr state))))))
458
459 (dimension ()
460 ;; `[' c-fragment ']'
461
462 (parse (seq ((frag (parse-delimited-fragment
463 scanner #\[ #\])))
464 (c-fragment-text frag))))
465
466 (lbracket ()
467 ;; Postfix: dimension+
468
469 (parse (seq ((dims (list (:min 1) (dimension))))
470 (postop "[]" (state 10)
471 (cons (lambda (type)
472 (funcall (car state)
473 (make-array-type type dims)))
474 (cdr state)))))))
475
476 ;; And now we actually do the declarator parsing.
477 (parse (seq ((value (expr (:nestedp nestedp)
478
479 ;; An actual operand.
480 (kernel)
481
482 ;; Binary operators. There aren't any.
483 nil
484
485 ;; Prefix operators.
486 (or (star)
487 (prefix-lparen))
488
489 ;; Postfix operators.
490 (or (postfix-lparen)
491 (lbracket)
492 (when nestedp (seq (#\)) (rparen #\))))))))
493 (cons (wrap-c-type (lambda (type)
494 (funcall (car value) type))
495 base-type)
496 (cdr value))))))))
497
498 ;;;----- That's all, folks --------------------------------------------------