chiark / gitweb /
a5969d47d3daa370ee166e7d8dd18b044445193d
[sod] / src / c-types-impl.lisp
1 ;;; -*-lisp-*-
2 ;;;
3 ;;; C type representation implementation
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 ;;; Interning types.
30
31 (defparameter *c-type-intern-map* (make-hash-table :test #'equal)
32   "Hash table mapping lists describing types to their distinguished
33    representations.")
34
35 (defun intern-c-type (class &rest initargs)
36   "If the CLASS and INITARGS have already been interned, then return the
37    existing object; otherwise make a new one."
38   (let ((list (cons (typecase class
39                       ;; Canonify the class object; we'd prefer a name.
40                       (standard-class (class-name class))
41                       (t class))
42                     (let ((alist nil) (plist initargs))
43                       ;; Canonify the initargs.  Arrange for them to be in
44                       ;; ascending order by name.  This is annoying because
45                       ;; a plist isn't a readily sortable sequence.
46                       (loop
47                         (when (null plist) (return))
48                         (let ((name (pop plist)) (value (pop plist)))
49                           (push (cons name value) alist)))
50                       (dolist (assoc (sort alist #'string> :key #'car))
51                         (push (cdr assoc) plist)
52                         (push (car assoc) plist))
53                       plist))))
54     (or (gethash list *c-type-intern-map*)
55         (let ((new (apply #'make-instance class initargs)))
56           (setf (gethash new *c-type-intern-map*) t
57                 (gethash list *c-type-intern-map*) new)))))
58
59 #+test
60 (defun check-type-intern-map ()
61   "Sanity check for the type-intern map."
62   (let ((map (make-hash-table)))
63
64     ;; Pass 1: check that interned types are consistent with their keys.
65     ;; Remember interned types.
66     (maphash (lambda (k v)
67                (when (listp k)
68                  (let ((ty (apply #'make-instance k)))
69                    (assert (c-type-equal-p ty v)))
70                  (setf (gethash v map) t)))
71              *c-type-intern-map*)
72
73     ;; Pass 2: check that the interned type indicators are correct.
74     (maphash (lambda (k v)
75                (declare (ignore v))
76                (assert (gethash k *c-type-intern-map*)))
77              map)
78     (maphash (lambda (k v)
79                (declare (ignore v))
80                (when (typep k 'c-type)
81                  (assert (gethash k map))))
82              *c-type-intern-map*)))
83
84 (defun make-or-intern-c-type (new-type-class base-types &rest initargs)
85   "Return a possibly-new instance of NEW-TYPE-CLASS with the given INITARGS.
86
87    If all of the BASE-TYPES are interned, then use `intern-c-type' to
88    construct the new type; otherwise just make a new one with
89    `make-instance'.  BASE-TYPES may be a singleton type, or a sequence of
90    types."
91   (apply (if (if (typep base-types 'sequence)
92                  (every (lambda (type)
93                           (gethash type *c-type-intern-map*))
94                         base-types)
95                  (gethash base-types *c-type-intern-map*))
96              #'intern-c-type #'make-instance)
97          new-type-class
98          initargs))
99
100 ;;;--------------------------------------------------------------------------
101 ;;; Qualifiers.
102
103 (defmethod c-qualifier-keyword ((qualifier (eql :atomic))) "_Atomic")
104
105 (defmethod qualify-c-type ((type qualifiable-c-type) qualifiers)
106   (let ((initargs (instance-initargs type)))
107     (remf initargs :qualifiers)
108     (apply #'make-or-intern-c-type (class-of type) type
109            :qualifiers (canonify-qualifiers
110                         (append qualifiers (c-type-qualifiers type)))
111            initargs)))
112
113 ;;;--------------------------------------------------------------------------
114 ;;; Storage specifiers.
115
116 (defmethod c-type-equal-p :around
117     ((type-a c-storage-specifiers-type) (type-b c-type))
118   "Ignore storage specifiers when comparing C types."
119   (c-type-equal-p (c-type-subtype type-a) type-b))
120
121 (defmethod c-type-equal-p :around
122     ((type-a c-type) (type-b c-storage-specifiers-type))
123   "Ignore storage specifiers when comparing C types."
124   (c-type-equal-p type-a (c-type-subtype type-b)))
125
126 (defun make-storage-specifiers-type (subtype specifiers)
127   "Construct a type based on SUBTYPE, carrying the storage SPECIFIERS."
128   (if (null specifiers) subtype
129       (make-or-intern-c-type 'c-storage-specifiers-type subtype
130                              :specifiers specifiers
131                              :subtype subtype)))
132
133 (defmethod pprint-c-type ((type c-storage-specifiers-type) stream kernel)
134   (dolist (spec (c-type-specifiers type))
135     (pprint-c-storage-specifier spec stream)
136     (write-char #\space stream)
137     (pprint-newline :miser stream))
138   (pprint-c-type (c-type-subtype type) stream kernel))
139
140 (defmethod print-c-type
141     (stream (type c-storage-specifiers-type) &optional colon atsign)
142   (declare (ignore colon atsign))
143   (format stream "~:@<SPECS ~@_~:I~/sod:print-c-type/~
144                             ~{ ~_~/sod:print-c-storage-specifier/~}~:>"
145           (c-type-subtype type) (c-type-specifiers type)))
146
147 (export 'specs)
148 (define-c-type-syntax specs (subtype &rest specifiers)
149   `(make-storage-specifiers-type
150     ,(expand-c-type-spec subtype)
151     (list ,@(mapcar #'expand-c-storage-specifier specifiers))))
152
153 ;;;--------------------------------------------------------------------------
154 ;;; Some storage specifiers.
155
156 (export 'alignas-storage-specifier)
157 (defclass alignas-storage-specifier ()
158   ((alignment :initarg :alignment :reader spec-alignment)))
159
160 (export 'alignas)
161 (define-c-storage-specifier-syntax alignas (alignment)
162   `(make-instance 'alignas-storage-specifier :alignment ,alignment))
163
164 (defmethod print-c-storage-specifier
165     (stream (spec alignas-storage-specifier) &optional colon atsign)
166   (declare (ignore colon atsign))
167   (format stream "~:@<~S ~_~S~:>" 'alignas (spec-alignment spec)))
168
169 (defmethod pprint-c-storage-specifier
170     ((spec alignas-storage-specifier) stream)
171   (format stream "_Alignas(~A)" (spec-alignment spec)))
172
173 ;;;--------------------------------------------------------------------------
174 ;;; Simple C types.
175
176 ;; Class definition.
177
178 (export '(simple-c-type c-type-name))
179 (defclass simple-c-type (qualifiable-c-type)
180   ((name :initarg :name :type string :reader c-type-name))
181   (:documentation
182    "C types with simple forms."))
183
184 ;; Constructor function and interning.
185
186 (export 'make-simple-type)
187 (defun make-simple-type (name &optional qualifiers)
188   "Make a distinguished object for the simple type called NAME."
189   (intern-c-type 'simple-c-type
190                  :name name
191                  :qualifiers (canonify-qualifiers qualifiers)))
192
193 ;; Comparison protocol.
194
195 (defmethod c-type-equal-p and
196     ((type-a simple-c-type) (type-b simple-c-type))
197   (string= (c-type-name type-a) (c-type-name type-b)))
198
199 ;; C syntax output protocol.
200
201 (defmethod pprint-c-type ((type simple-c-type) stream kernel)
202   (pprint-logical-block (stream nil)
203     (format stream "~{~A ~@_~}~A"
204             (c-type-qualifier-keywords type)
205             (c-type-name type))
206     (funcall kernel stream 0 t)))
207
208 ;; S-expression notation protocol.
209
210 (defparameter *simple-type-map* (make-hash-table :test #'equal)
211   "Hash table mapping strings of C syntax to symbolic names.")
212
213 (defmethod print-c-type (stream (type simple-c-type) &optional colon atsign)
214   (declare (ignore colon atsign))
215   (let* ((name (c-type-name type))
216          (symbol (gethash name *simple-type-map*)))
217     (format stream "~:[~S~;~:@<~S~0@*~{ ~_~S~}~:>~]"
218             (c-type-qualifiers type) (or symbol name))))
219
220 (eval-when (:compile-toplevel :load-toplevel :execute)
221   (defmethod expand-c-type-spec ((spec string))
222     `(make-simple-type ,spec))
223   (defmethod expand-c-type-form ((head string) tail)
224     `(make-simple-type ,head (list ,@tail))))
225
226 (export 'define-simple-c-type)
227 (defmacro define-simple-c-type (names type &key export)
228   "Define each of NAMES to be a simple type called TYPE."
229   (let ((names (if (listp names) names (list names)))
230         (types (if (listp type) type (list type))))
231     (with-gensyms (type name)
232       `(progn
233          (dolist (,type ',types)
234            (setf (gethash ,type *simple-type-map*) ',(car names)))
235          (dolist (,name ',names)
236            (setf (gethash ,name *simple-type-map*) ,(car types)))
237          (defctype ,names ,(car types) :export ,export)
238          (define-c-type-syntax ,(car names) (&rest quals)
239            `(make-simple-type ,',(car types) (list ,@quals)))))))
240
241 (export 'find-simple-c-type)
242 (defun find-simple-c-type (name)
243   "Return the `simple-c-type' with the given NAME, or nil."
244   (aand (gethash name *simple-type-map*)
245         (make-simple-type (gethash it *simple-type-map*))))
246
247 ;; Built-in C types.
248
249 (define-simple-c-type void "void" :export t)
250
251 (define-simple-c-type char "char" :export t)
252 (define-simple-c-type (unsigned-char uchar) "unsigned char" :export t)
253 (define-simple-c-type (signed-char schar) "signed char" :export t)
254 (define-simple-c-type wchar-t "wchar_t" :export t)
255
256 (define-simple-c-type (int signed signed-int sint)
257   ("int" "signed") :export t)
258 (define-simple-c-type (unsigned unsigned-int uint) "unsigned" :export t)
259
260 (define-simple-c-type (short signed-short short-int signed-short-int sshort)
261   "short" :export t)
262 (define-simple-c-type (unsigned-short unsigned-short-int ushort)
263   "unsigned short" :export t)
264
265 (define-simple-c-type (long signed-long long-int signed-long-int slong)
266   "long" :export t)
267 (define-simple-c-type (unsigned-long unsigned-long-int ulong)
268   "unsigned long" :export t)
269
270 (define-simple-c-type (long-long signed-long-long long-long-int
271                        signed-long-long-int llong sllong)
272   "long long" :export t)
273 (define-simple-c-type (unsigned-long-long unsigned-long-long-int ullong)
274   "unsigned long long" :export t)
275
276 (define-simple-c-type float "float" :export t)
277 (define-simple-c-type double "double" :export t)
278 (define-simple-c-type long-double "long double" :export t)
279
280 (define-simple-c-type bool ("_Bool" "bool") :export t)
281
282 (define-simple-c-type float-complex "float _Complex" :export t)
283 (define-simple-c-type double-complex "double _Complex" :export t)
284 (define-simple-c-type long-double-complex "long double _Complex" :export t)
285
286 (define-simple-c-type float-imaginary "float _Imaginary" :export t)
287 (define-simple-c-type double-imaginary "double _Imaginary" :export t)
288 (define-simple-c-type long-double-imaginary
289     "long double _Imaginary" :export t)
290
291 (define-simple-c-type va-list "va_list" :export t)
292 (define-simple-c-type size-t "size_t" :export t)
293 (define-simple-c-type ptrdiff-t "ptrdiff_t" :export t)
294
295 ;;;--------------------------------------------------------------------------
296 ;;; Tagged types (enums, structs and unions).
297
298 ;; Class definition.
299
300 (export '(tagged-c-type c-type-tag))
301 (defclass tagged-c-type (qualifiable-c-type)
302   ((tag :initarg :tag :type string :reader c-type-tag))
303   (:documentation
304    "C types with tags."))
305
306 ;; Subclass definitions.
307
308 (export 'c-tagged-type-kind)
309 (defgeneric c-tagged-type-kind (type)
310   (:documentation
311    "Return the kind of tagged type that TYPE is, as a keyword."))
312
313 (export 'kind-c-tagged-type)
314 (defgeneric kind-c-tagged-type (kind)
315   (:documentation
316    "Given a keyword KIND, return the appropriate class name."))
317
318 (export 'make-c-tagged-type)
319 (defun make-c-tagged-type (kind tag &optional qualifiers)
320   "Return a tagged type with the given KIND (keyword) and TAG (string)."
321   (intern-c-type (kind-c-tagged-type kind)
322                  :tag tag
323                  :qualifiers (canonify-qualifiers qualifiers)))
324
325 (macrolet ((define-tagged-type (kind what)
326              (let* ((type (symbolicate 'c- kind '-type))
327                     (keyword (intern (symbol-name kind) :keyword))
328                     (constructor (symbolicate 'make- kind '-type)))
329                `(progn
330                   (export '(,type ,kind ,constructor))
331                   (defclass ,type (tagged-c-type) ()
332                     (:documentation ,(format nil "C ~A types." what)))
333                   (defmethod c-tagged-type-kind ((type ,type))
334                     ',keyword)
335                   (defmethod kind-c-tagged-type ((kind (eql ',keyword)))
336                     ',type)
337                   (defun ,constructor (tag &optional qualifiers)
338                     (intern-c-type ',type :tag tag
339                                    :qualifiers (canonify-qualifiers
340                                                 qualifiers)))
341                   (define-c-type-syntax ,kind (tag &rest quals)
342                     ,(format nil "Construct ~A type named TAG" what)
343                     `(,',constructor ,tag (list ,@quals)))))))
344   (define-tagged-type enum "enumerated")
345   (define-tagged-type struct "structure")
346   (define-tagged-type union "union"))
347
348 ;; Comparison protocol.
349
350 (defmethod c-type-equal-p and ((type-a tagged-c-type) (type-b tagged-c-type))
351   (string= (c-type-tag type-a) (c-type-tag type-b)))
352
353 ;; C syntax output protocol.
354
355 (defmethod pprint-c-type ((type tagged-c-type) stream kernel)
356   (pprint-logical-block (stream nil)
357     (format stream "~{~A ~@_~}~(~A~) ~A"
358             (c-type-qualifier-keywords type)
359             (c-tagged-type-kind type)
360             (c-type-tag type))
361     (funcall kernel stream 0 t)))
362
363 ;; S-expression notation protocol.
364
365 (defmethod print-c-type (stream (type tagged-c-type) &optional colon atsign)
366   (declare (ignore colon atsign))
367   (format stream "~:@<~S ~@_~S~{ ~_~S~}~:>"
368           (c-tagged-type-kind type)
369           (c-type-tag type)
370           (c-type-qualifiers type)))
371
372 ;;;--------------------------------------------------------------------------
373 ;;; Atomic types.
374
375 ;; Class definition.
376
377 (export 'c-atomic-type)
378 (defclass c-atomic-type (qualifiable-c-type)
379   ((subtype :initarg :subtype :type c-type :reader c-type-subtype))
380   (:documentation "C atomic types."))
381
382 ;; Constructor function.
383
384 (export 'make-atomic-type)
385 (defun make-atomic-type (subtype &optional qualifiers)
386   "Return a (maybe distinguished) atomic type."
387   (make-or-intern-c-type 'c-atomic-type subtype
388                          :subtype subtype
389                          :qualifiers (canonify-qualifiers qualifiers)))
390
391 ;; Comparison protocol.
392
393 (defmethod c-type-equal-p and ((type-a c-atomic-type) (type-b c-atomic-type))
394   (c-type-equal-p (c-type-subtype type-a) (c-type-subtype type-b)))
395
396 ;; C-syntax output protocol.
397
398 (defmethod pprint-c-type ((type c-atomic-type) stream kernel)
399   (pprint-logical-block (stream nil)
400     (format stream "~{~A ~@_~}" (c-type-qualifier-keywords type))
401     (write-string "_Atomic(" stream)
402     (pprint-indent :current 0 stream)
403     (pprint-c-type (c-type-subtype type) stream
404                    (lambda (stream prio spacep)
405                      (declare (ignore stream prio spacep))))
406     (write-char #\) stream)))
407
408 ;; S-expression notation protocol.
409
410 (defmethod print-c-type (stream (type c-atomic-type) &optional colon atsign)
411   (declare (ignore colon atsign))
412   (format stream "~:@<ATOMIC ~@_~/sod:print-c-type/~{ ~_~S~}~:>"
413           (c-type-subtype type)
414           (c-type-qualifiers type)))
415
416 (export 'atomic)
417 (define-c-type-syntax atomic (sub &rest quals)
418   "Return the type of atomic SUB."
419   `(make-atomic-type ,(expand-c-type-spec sub) (list ,@quals)))
420
421 ;;;--------------------------------------------------------------------------
422 ;;; Pointer types.
423
424 ;; Class definition.
425
426 (export 'c-pointer-type)
427 (defclass c-pointer-type (qualifiable-c-type)
428   ((subtype :initarg :subtype :type c-type :reader c-type-subtype))
429   (:documentation "C pointer types."))
430
431 ;; Constructor function.
432
433 (export 'make-pointer-type)
434 (defun make-pointer-type (subtype &optional qualifiers)
435   "Return a (maybe distinguished) pointer type."
436   (make-or-intern-c-type 'c-pointer-type subtype
437                          :subtype subtype
438                          :qualifiers (canonify-qualifiers qualifiers)))
439
440 ;; Comparison protocol.
441
442 (defmethod c-type-equal-p and ((type-a c-pointer-type)
443                                (type-b c-pointer-type))
444   (c-type-equal-p (c-type-subtype type-a) (c-type-subtype type-b)))
445
446 ;; C syntax output protocol.
447
448 (defmethod pprint-c-type ((type c-pointer-type) stream kernel)
449   (pprint-c-type (c-type-subtype type) stream
450                  (lambda (stream prio spacep)
451                    (when spacep (c-type-space stream))
452                    (maybe-in-parens (stream (> prio 1))
453                      (format stream "*~{~A~^ ~@_~}"
454                              (c-type-qualifier-keywords type))
455                      (funcall kernel stream 1 (c-type-qualifiers type))))))
456
457 ;; S-expression notation protocol.
458
459 (defmethod print-c-type (stream (type c-pointer-type) &optional colon atsign)
460   (declare (ignore colon atsign))
461   (format stream "~:@<* ~@_~/sod:print-c-type/~{ ~_~S~}~:>"
462           (c-type-subtype type)
463           (c-type-qualifiers type)))
464
465 (export '(* pointer ptr))
466 (define-c-type-syntax * (sub &rest quals)
467   "Return the type of pointer-to-SUB."
468   `(make-pointer-type ,(expand-c-type-spec sub) (list ,@quals)))
469 (c-type-alias * pointer ptr)
470
471 ;; Built-in C types.
472
473 (export '(string const-string))
474 (defctype string (* char))
475 (defctype const-string (* (char :const)))
476
477 ;;;--------------------------------------------------------------------------
478 ;;; Array types.
479
480 ;; Class definition.
481
482 (export '(c-array-type c-array-dimensions))
483 (defclass c-array-type (c-type)
484   ((subtype :initarg :subtype :type c-type :reader c-type-subtype)
485    (dimensions :initarg :dimensions :type list :reader c-array-dimensions))
486   (:documentation
487    "C array types."))
488
489 ;; Constructor function.
490
491 (export 'make-array-type)
492 (defun make-array-type (subtype dimensions)
493   "Return a new array of SUBTYPE with given DIMENSIONS."
494   (make-instance 'c-array-type :subtype subtype
495                  :dimensions (or dimensions '(nil))))
496
497 ;; Comparison protocol.
498
499 (defmethod c-type-equal-p and ((type-a c-array-type) (type-b c-array-type))
500
501   ;; Messy.  C doesn't have multidimensional arrays, but we fake them for
502   ;; convenience's sake.  But it means that we have to arrange for
503   ;; multidimensional arrays to equal vectors of vectors -- and in general
504   ;; for multidimensional arrays of multidimensional arrays to match each
505   ;; other properly, even when their dimensions don't align precisely.
506   (labels ((check (sub-a dim-a sub-b dim-b)
507              (cond ((endp dim-a)
508                     (cond ((endp dim-b)
509                            (c-type-equal-p sub-a sub-b))
510                           ((typep sub-a 'c-array-type)
511                            (check (c-type-subtype sub-a)
512                                   (c-array-dimensions sub-a)
513                                   sub-b dim-b))
514                           (t
515                            nil)))
516                    ((endp dim-b)
517                     (check sub-b dim-b sub-a dim-a))
518                    ((equal (car dim-a) (car dim-b))
519                     (check sub-a (cdr dim-a) sub-b (cdr dim-b)))
520                    (t
521                     nil))))
522     (check (c-type-subtype type-a) (c-array-dimensions type-a)
523            (c-type-subtype type-b) (c-array-dimensions type-b))))
524
525 ;; C syntax output protocol.
526
527 (defmethod pprint-c-type ((type c-array-type) stream kernel)
528   (pprint-c-type (c-type-subtype type) stream
529                  (lambda (stream prio spacep)
530                    (maybe-in-parens (stream (> prio 2))
531                      (funcall kernel stream 2 spacep)
532                      (format stream "~@<~{[~@[~A~]]~^~_~}~:>"
533                              (c-array-dimensions type))))))
534
535 ;; S-expression notation protocol.
536
537 (defmethod print-c-type (stream (type c-array-type) &optional colon atsign)
538   (declare (ignore colon atsign))
539   (format stream "~:@<[] ~@_~:I~/sod:print-c-type/~{ ~_~S~}~:>"
540           (c-type-subtype type)
541           (c-array-dimensions type)))
542
543 (export '([] array vec))
544 (define-c-type-syntax [] (sub &rest dims)
545   "Return the type of arrays of SUB with the dimensions DIMS.
546
547    If the DIMS are omitted, a single unknown-length dimension is added."
548   `(make-array-type ,(expand-c-type-spec sub)
549                     (list ,@(or dims '(nil)))))
550 (c-type-alias [] array vec)
551
552 ;;;--------------------------------------------------------------------------
553 ;;; Function types.
554
555 ;; Function arguments.
556
557 (defun argument-lists-equal-p (list-a list-b)
558   "Return whether LIST-A and LIST-B match.
559
560    They must have the same number of arguments, and each argument must have
561    the same type, or be `:ellipsis'.  The argument names are not inspected."
562   (and (= (length list-a) (length list-b))
563        (every (lambda (arg-a arg-b)
564                 (if (eq arg-a :ellipsis)
565                     (eq arg-b :ellipsis)
566                     (and (argumentp arg-a) (argumentp arg-b)
567                          (c-type-equal-p (argument-type arg-a)
568                                          (argument-type arg-b)))))
569               list-a list-b)))
570
571 (defun fix-and-check-keyword-argument-list (list)
572   "Check the keyword argument LIST is valid; if so, fix it up and return it.
573
574    Check that the keyword arguments have distinct names.  Fix the list up by
575    sorting it by keyword name."
576
577   (unless (every #'argumentp list)
578     (error "(INTERNAL) not an argument value"))
579
580   (let ((list (sort (copy-list list) #'string< :key #'argument-name)))
581     (do ((list (cdr list) (cdr list))
582          (this (car list) (car list))
583          (prev nil this))
584         ((endp list))
585       (when prev
586         (let ((this-name (argument-name this))
587               (prev-name (argument-name prev)))
588           (when (string= this-name prev-name)
589             (error "Duplicate keyword argument name `~A'" this-name)))))
590     list))
591
592 (export 'merge-keyword-lists)
593 (defun merge-keyword-lists (whatfn lists)
594   "Return the union of keyword argument lists.
595
596    The WHATFN is either nil or a designator for a function (see below).
597
598    The LISTS parameter consists of pairs (REPORTFN . ARGS), where REPORTFN is
599    either nil or a designator for a function (see below); and and ARGS is a
600    list of `argument' objects.
601
602    The resulting list contains exactly one argument for each distinct
603    argument name appearing in the input lists; this argument will contain the
604    default value corresponding to the name's earliest occurrence in the input
605    LISTS.
606
607    If the same name appears in multiple input lists with different types, a
608    continuable error is signalled.
609
610    The WHATFN function is given no arguments, and is expected to return a
611    file location (or other object convertible with `file-location'), and a
612    string (or other printable object) describing the site at which the
613    keyword argument lists are being merged or nil; a mismatch error will be
614    reported as being at the location returned by WHATFN, and the description
615    will be included in the error message.  A nil WHATFN is equivalent to a
616    function which returns a nil location and description, though this is
617    considered poor practice.
618
619    The REPORTFN is given a single argument ARG, which is one of the
620    conflicting `argument' objects found in the REPORTFN's corresponding
621    argument list: the REPORTFN is expected to issue additional `info'
622    messages to help the user diagnose the problem.  The (common) name of the
623    argument has already been reported.  A nil REPORTFN is equivalent to one
624    which does nothing, though this is considered poor practice."
625
626   ;; The easy way through all of this is with a hash table mapping argument
627   ;; names to (WHAT . ARG) pairs.
628
629   (let ((argmap (make-hash-table :test #'equal)))
630
631     ;; Set up the table.  When we find a duplicate, check that the types
632     ;; match.
633     (dolist (item lists)
634       (let ((reportfn (car item))
635             (args (cdr item)))
636         (dolist (arg args)
637           (let* ((name (argument-name arg))
638                  (other-item (gethash name argmap)))
639             (if (null other-item)
640                 (setf (gethash name argmap) (cons reportfn arg))
641                 (let* ((type (argument-type arg))
642                        (other-reportfn (car other-item))
643                        (other (cdr other-item))
644                        (other-type (argument-type other)))
645                   (unless (c-type-equal-p type other-type)
646                     (multiple-value-bind (floc desc)
647                         (if whatfn (funcall whatfn) (values nil nil))
648                       (cerror*-with-location floc
649                                              "Type mismatch for keyword ~
650                                               argument `~A'~@[ in ~A~]"
651                                              name desc)
652                       (when reportfn
653                         (funcall reportfn arg))
654                       (when other-reportfn
655                         (funcall other-reportfn other))))))))))
656
657     ;; Now it's just a matter of picking the arguments out again.
658     (let ((result nil))
659       (maphash (lambda (name item)
660                  (declare (ignore name))
661                  (push (cdr item) result))
662                argmap)
663       (fix-and-check-keyword-argument-list result))))
664
665 ;; Class definition.
666
667 (export '(c-function-type c-function-arguments))
668 (defclass c-function-type (c-type)
669   ((subtype :initarg :subtype :type c-type :reader c-type-subtype)
670    (arguments :type list :reader c-function-arguments))
671   (:documentation
672    "C function types.  The subtype is the return type, as implied by the C
673     syntax for function declarations."))
674
675 (defmethod shared-initialize :after
676     ((type c-function-type) slot-names &key (arguments nil argsp))
677   (declare (ignore slot-names))
678   (when argsp
679     (setf (slot-value type 'arguments)
680           (if (and arguments
681                    (null (cdr arguments))
682                    (not (eq (car arguments) :ellipsis))
683                    (eq (argument-type (car arguments)) c-type-void))
684               nil
685               arguments))))
686
687 (export '(c-keyword-function-type c-function-keywords))
688 (defclass c-keyword-function-type (c-function-type)
689   ((keywords :initarg :keywords :type list
690              :reader c-function-keywords))
691   (:documentation
692    "C function types for `functions' which take keyword arguments."))
693
694 (defmethod shared-initialize :after
695     ((type c-keyword-function-type) slot-names &key (keywords nil keysp))
696   (declare (ignore slot-names))
697   (when keysp
698     (setf (slot-value type 'keywords)
699           (fix-and-check-keyword-argument-list keywords))))
700
701 ;; Constructor function.
702
703 (export 'make-function-type)
704 (defun make-function-type (subtype arguments)
705   "Return a new function type, returning SUBTYPE and accepting ARGUMENTS.
706
707    As a helper for dealing with the S-expression syntax for keyword
708    functions, if ARGUMENTS has the form (ARGS ... :keys KEYWORDS ...)' then
709    return a keyword function with arguments (ARGS ...) and keywords (KEYWORDS
710    ...)."
711   (let ((split (member :keys arguments)))
712     (if split
713         (make-instance 'c-keyword-function-type
714                        :subtype subtype
715                        :arguments (ldiff arguments split)
716                        :keywords (cdr split))
717         (make-instance 'c-function-type
718                        :subtype subtype
719                        :arguments arguments))))
720
721 (export 'make-keyword-function-type)
722 (defun make-keyword-function-type (subtype arguments keywords)
723   "Return a new keyword-function type, returning SUBTYPE and accepting
724    ARGUMENTS and KEYWORDS."
725   (make-instance 'c-keyword-function-type :subtype subtype
726                  :arguments arguments :keywords keywords))
727
728 ;; Comparison protocol.
729
730 (defmethod c-type-equal-p and
731     ((type-a c-function-type) (type-b c-function-type))
732   (and (c-type-equal-p (c-type-subtype type-a) (c-type-subtype type-b))
733        (argument-lists-equal-p (c-function-arguments type-a)
734                                (c-function-arguments type-b))))
735
736 (defmethod c-type-equal-p and
737     ((type-a c-keyword-function-type) (type-b c-keyword-function-type))
738   ;; Actually, there's nothing to check here.  I'm happy as long as both
739   ;; functions notionally accept keyword arguments.
740   t)
741
742 ;; C syntax output protocol.
743
744 (export 'pprint-c-function-type)
745 (defun pprint-c-function-type (return-type stream print-args print-kernel)
746   "Common top-level printing for function types.
747
748    Prints RETURN-TYPE (KERNEL(ARGS)), where RETURN-TYPE is the actual return
749    type, and ARGS and KERNEL are whatever is printed by the PRINT-ARGS and
750    PRINT-KERNEL functions.
751
752    The PRINT-KERNEL function is the standard such thing for the
753    `pprint-c-type' protocol; PRINT-ARGS accepts just an output stream."
754   (pprint-c-type return-type stream
755                  (lambda (stream prio spacep)
756                    (maybe-in-parens (stream (> prio 2))
757                      (when spacep (c-type-space stream))
758                      (funcall print-kernel stream 2 nil)
759                      (pprint-indent :block 4 stream)
760                      (pprint-newline :linear stream)
761                      (pprint-logical-block
762                          (stream nil :prefix "(" :suffix ")")
763                        (funcall print-args stream))))))
764
765 (export 'pprint-argument-list)
766 (defun pprint-argument-list (args stream)
767   "Print an argument list.
768
769    The ARGS is a list of `argument' objects, optionally containing an
770    `:ellipsis' marker.  The output is written to STREAM.
771
772    Returns non-nil if any arguments were actually printed."
773   (let ((anyp nil))
774     (pprint-logical-block (stream nil)
775       (dolist (arg args)
776         (if anyp
777             (format stream ", ~_")
778             (setf anyp t))
779         (etypecase arg
780           ((member :ellipsis)
781            (write-string "..." stream))
782           (argument
783            (pprint-logical-block (stream nil)
784              (pprint-c-type (argument-type arg) stream (argument-name arg))
785              (let ((default (argument-default arg)))
786                (when default
787                  (format stream " = ~2I~_~A" default))))))))
788     anyp))
789
790 (let ((void-arglist (list (make-argument nil c-type-void))))
791   (defmethod pprint-c-type ((type c-function-type) stream kernel)
792     (let ((args (or (c-function-arguments type) void-arglist)))
793       (pprint-c-function-type (c-type-subtype type) stream
794                               (lambda (stream)
795                                 (pprint-argument-list args stream))
796                               kernel))))
797
798 (defmethod pprint-c-type ((type c-keyword-function-type) stream kernel)
799   (let ((args (c-function-arguments type))
800         (keys (c-function-keywords type)))
801     (pprint-c-function-type  (c-type-subtype type) stream
802                                (lambda (stream)
803                                  (when (pprint-argument-list args stream)
804                                    (format stream ", ~_"))
805                                  (write-char #\? stream)
806                                  (pprint-argument-list keys stream))
807                                kernel)))
808
809 ;; S-expression notation protocol.
810
811 (defmethod print-c-type
812     (stream (type c-function-type) &optional colon atsign)
813   (declare (ignore colon atsign))
814   (format stream "~:@<~
815                   FUN ~@_~:I~
816                   ~/sod:print-c-type/~:[~; ~]~:*~_~
817                   ~<~@{~:<~S ~@_~/sod:print-c-type/~:>~^ ~_~}~:>~
818                   ~:[~2*~; ~_~S ~@_~<~@{~:<~S ~@_~/sod:print-c-type/~
819                     ~@[ ~@_~S~]~:>~^ ~_~}~:>~]~
820                   ~:>"
821           (c-type-subtype type)
822           (mapcar (lambda (arg)
823                     (if (eq arg :ellipsis) arg
824                         (list (argument-name arg) (argument-type arg))))
825                   (c-function-arguments type))
826           (typep type 'c-keyword-function-type)
827           :keys
828           (and (typep type 'c-keyword-function-type)
829                (mapcar (lambda (arg)
830                          (list (argument-name arg)
831                                (argument-type arg)
832                                (argument-default arg)))
833                        (c-function-keywords type)))))
834
835 (export '(fun function () func fn))
836 (define-c-type-syntax fun (ret &rest args)
837   "Return the type of functions which returns RET and has arguments ARGS.
838
839    The ARGS are a list of arguments of the form (NAME TYPE [DEFAULT]).  The
840    NAME can be NIL to indicate that no name was given.
841
842    If an entry isn't a list, it's assumed to be the start of a Lisp
843    expression to compute the tail of the list; similarly, if the list is
844    improper, then it's considered to be a complete expression.  The upshot of
845    this apparently bizarre rule is that you can say
846
847      (c-type (fun int (\"foo\" int) . arg-tail))
848
849    where ARG-TAIL is (almost) any old Lisp expression and have it tack the
850    arguments onto the end.  Of course, there don't have to be any explicit
851    arguments at all.  The only restriction is that the head of the Lisp form
852    can't be a list -- so ((lambda (...) ...) ...) is out, but you probably
853    wouldn't type that anyway."
854
855   `(make-function-type ,(expand-c-type-spec ret)
856                        ,(do ((args args (cdr args))
857                              (list nil
858                                    (if (keywordp (car args))
859                                        (cons (car args) list)
860                                        (let* ((name (caar args))
861                                               (type (expand-c-type-spec
862                                                      (cadar args)))
863                                               (default (and (cddar args)
864                                                             (caddar args)))
865                                               (arg `(make-argument
866                                                      ,name ,type ,default)))
867                                          (cons arg list)))))
868                             ((or (atom args)
869                                  (and (atom (car args))
870                                       (not (keywordp (car args)))))
871                              (cond ((and (null args) (null list)) `nil)
872                                    ((null args) `(list ,@(nreverse list)))
873                                    ((null list) `,args)
874                                    (t `(list* ,@(nreverse list) ,args)))))))
875 (c-type-alias fun function () func fn)
876
877 ;; Additional utilities for dealing with functions.
878
879 (export 'commentify-argument-names)
880 (defun commentify-argument-names (arguments)
881   "Return an argument list with the arguments commentified.
882
883    That is, with each argument name passed through
884    `commentify-argument-name'."
885   (mapcar (lambda (arg)
886             (if (eq arg :ellipsis) arg
887                 (make-argument (commentify-argument-name (argument-name arg))
888                                (argument-type arg)
889                                (argument-default arg))))
890           arguments))
891
892 (export 'commentify-function-type)
893 (defun commentify-function-type (type)
894   "Return a type like TYPE, but with arguments commentified.
895
896    This doesn't recurse into the return type or argument types."
897   (make-function-type (c-type-subtype type)
898                       (commentify-argument-names
899                        (c-function-arguments type))))
900
901 (export 'reify-variable-argument-tail)
902 (defun reify-variable-argument-tail (arguments)
903   "Replace any `:ellipsis' item in ARGUMENTS with a `va_list' argument.
904
905    The argument's name is taken from the variable `*sod-ap*'."
906   (substitute (make-argument *sod-ap* c-type-va-list) :ellipsis arguments))
907
908 ;;;----- That's all, folks --------------------------------------------------