chiark / gitweb /
It lives!
[sod] / lex.lisp
1 ;;; -*-lisp-*-
2 ;;;
3 ;;; Lexical analysis of a vaguely C-like language
4 ;;;
5 ;;; (c) 2009 Straylight/Edgeware
6 ;;;
7
8 ;;;----- Licensing notice ---------------------------------------------------
9 ;;;
10 ;;; This file is part of the Simple Object Definition system.
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 ;;; Basic lexical analyser infrastructure.
30
31 ;; Class definition.
32
33 (defclass lexer ()
34   ((stream :initarg :stream :type stream :reader lexer-stream)
35    (char :initform nil :type (or character null) :reader lexer-char)
36    (pushback-chars :initform nil :type list)
37    (token-type :initform nil :accessor token-type)
38    (token-value :initform nil :accessor token-value)
39    (pushback-tokens :initform nil :type list))
40   (:documentation
41    "Base class for lexical analysers.
42
43    The lexer reads characters from STREAM, which, for best results, wants to
44    be a POSITION-AWARE-INPUT-STREAM.
45
46    The lexer provides one-character lookahead by default: the current
47    lookahead character is available to subclasses in the slot CHAR.  Before
48    beginning lexical analysis, the lookahead character needs to be
49    established with NEXT-CHAR.  If one-character lookahead is insufficient,
50    the analyser can push back an arbitrary number of characters using
51    PUSHBACK-CHAR.
52
53    The NEXT-TOKEN function scans and returns the next token from the STREAM,
54    and makes it available as TOKEN-TYPE and TOKEN-VALUE, providing one-token
55    lookahead.  A parser using the lexical analyser can push back tokens using
56    PUSHBACK-TOKENS.
57
58    For convenience, the lexer implements a FILE-LOCATION method (delegated to
59    the underlying stream)."))
60
61 ;; Lexer protocol.
62
63 (defgeneric scan-token (lexer)
64   (:documentation
65    "Internal function for scanning tokens from an input stream.
66
67    Implementing a method on this function is the main responsibility of LEXER
68    subclasses; it is called by the user-facing NEXT-TOKEN function.
69
70    The method should consume characters (using NEXT-CHAR) as necessary, and
71    return two values: a token type and token value.  These will be stored in
72    the corresponding slots in the lexer object in order to provide the user
73    with one-token lookahead."))
74
75 (defgeneric next-token (lexer)
76   (:documentation
77    "Scan a token from an input stream.
78
79    This function scans a token from an input stream.  Two values are
80    returned: a `token type' and a `token value'.  These are opaque to the
81    LEXER base class, but the intent is that the token type be significant to
82    determining the syntax of the input, while the token value carries any
83    additional information about the token's semantic content.  The token type
84    and token value are also made available for lookahead via accessors
85    TOKEN-TYPE and TOKEN-NAME on the LEXER object.
86
87    If tokens have been pushed back (see PUSHBACK-TOKEN) then they are
88    returned one by one instead of scanning the stream.")
89
90   (:method ((lexer lexer))
91     (with-slots (pushback-tokens token-type token-value) lexer
92       (setf (values token-type token-value)
93             (if pushback-tokens
94                 (let ((pushback (pop pushback-tokens)))
95                   (values (car pushback) (cdr pushback)))
96                 (scan-token lexer))))))
97
98 (defgeneric pushback-token (lexer token-type &optional token-value)
99   (:documentation
100    "Push a token back into the lexer.
101
102    Make the given TOKEN-TYPE and TOKEN-VALUE be the current lookahead token.
103    The previous lookahead token is pushed down, and will be made available
104    agan once this new token is consumed by NEXT-TOKEN.  The FILE-LOCATION is
105    not affected by pushing tokens back.  The TOKEN-TYPE and TOKEN-VALUE be
106    anything at all: for instance, they need not be values which can actually
107    be returned by NEXT-TOKEN.")
108
109   (:method ((lexer lexer) new-token-type &optional new-token-value)
110     (with-slots (pushback-tokens token-type token-value) lexer
111       (push (cons token-type token-value) pushback-tokens)
112       (setf token-type new-token-type
113             token-value new-token-value))))
114
115 (defgeneric next-char (lexer)
116   (:documentation
117    "Fetch the next character from the LEXER's input stream.
118
119    Read a character from the input stream, and store it in the LEXER's CHAR
120    slot.  The character stored is returned.  If characters have been pushed
121    back then pushed-back characters are used instead of the input stream.
122
123    (This function is primarily intended for the use of lexer subclasses.)")
124
125   (:method ((lexer lexer))
126     (with-slots (stream char pushback-chars) lexer
127       (setf char (if pushback-chars
128                      (pop pushback-chars)
129                      (read-char stream nil))))))
130
131 (defgeneric pushback-char (lexer char)
132   (:documentation
133    "Push the CHAR back into the lexer.
134
135    Make CHAR be the current lookahead character (stored in the LEXER's CHAR
136    slot).  The previous lookahead character is pushed down, and will be made
137    available again once this character is consumed by NEXT-CHAR.
138
139    (This function is primarily intended for the use of lexer subclasses.)")
140
141   (:method ((lexer lexer) new-char)
142     (with-slots (char pushback-chars) lexer
143       (push char pushback-chars)
144       (setf char new-char))))
145
146 (defgeneric fixup-stream* (lexer thunk)
147   (:documentation
148    "Helper function for WITH-LEXER-STREAM.
149
150    This function does the main work for WITH-LEXER-STREAM.  The THUNK is
151    invoked on a single argument, the LEXER's underlying STREAM.")
152
153   (:method ((lexer lexer) thunk)
154     (with-slots (stream char pushback-chars) lexer
155       (when pushback-chars
156         (error "Lexer has pushed-back characters."))
157       (unread-char char stream)
158       (unwind-protect
159            (funcall thunk stream)
160         (setf char (read-char stream nil))))))
161
162 (defmacro with-lexer-stream ((streamvar lexer) &body body)
163   "Evaluate BODY with STREAMVAR bound to the LEXER's input stream.
164
165    The STREAM is fixed up so that the next character read (e.g., using
166    READ-CHAR) will be the lexer's current lookahead character.  Once the BODY
167    completes, the next character in the stream is read and set as the
168    lookahead character.  It is an error if the lexer has pushed-back
169    characters (since these can't be pushed back into the input stream
170    properly)."
171
172   `(fixup-stream* ,lexer
173                   (lambda (,streamvar)
174                     ,@body)))
175
176 (defmethod file-location ((lexer lexer))
177   (with-slots (stream) lexer
178     (file-location stream)))
179
180 (defgeneric skip-spaces (lexer)
181   (:documentation
182    "Skip over whitespace characters in the LEXER.")
183   (:method ((lexer lexer))
184     (do ((ch (lexer-char lexer) (next-char lexer)))
185         ((not (whitespace-char-p ch))))))
186
187 ;;;--------------------------------------------------------------------------
188 ;;; Lexer utilities.
189
190 (defun require-token
191     (lexer wanted-token-type &key (errorp t) (consumep t) default)
192   (with-slots (token-type token-value) lexer
193     (cond ((eql token-type wanted-token-type)
194            (prog1 token-value
195              (when consumep (next-token lexer))))
196           (errorp
197            (cerror* "Expected ~A but found ~A"
198                     (format-token wanted-token-type)
199                     (format-token token-type token-value))
200            default)
201           (t
202            default))))
203
204 ;;;--------------------------------------------------------------------------
205 ;;; Our main lexer.
206
207 (defun make-keyword-table (&rest keywords)
208   "Construct a keyword table for the lexical analyser.
209
210    The KEYWORDS arguments are individual keywords, either as strings or as
211    (WORD . VALUE) pairs.  A string argument is equivalent to a pair listing
212    the string itself as WORD and the corresponding keyword symbol (forced to
213    uppercase) as the VALUE."
214
215   (let ((table (make-hash-table :test #'equal)))
216     (dolist (item keywords)
217       (multiple-value-bind (word keyword)
218           (if (consp item)
219               (values (car item) (cdr item))
220               (values item (intern (string-upcase item) :keyword)))
221         (setf (gethash word table) keyword)))
222     table))
223
224 (defparameter *sod-keywords*
225   (make-keyword-table
226
227    ;; Words with a meaning to C's type system.
228    "char" "int" "float" "void"
229    "long" "short" "signed" "unsigned" "double"
230    "const" "volatile" "restrict"
231    "struct" "union" "enum"))
232
233 (defclass sod-lexer (lexer)
234   ()
235   (:documentation
236    "Lexical analyser for the SOD lanuage.
237
238    See the LEXER class for the gory details about the lexer protocol."))
239
240 (defun format-token (token-type &optional token-value)
241   (when (typep token-type 'lexer)
242     (let ((lexer token-type))
243       (setf token-type (token-type lexer)
244             token-value (token-value lexer))))
245   (etypecase token-type
246     ((eql :eof) "<end-of-file>")
247     ((eql :string) "<string-literal>")
248     ((eql :char) "<character-literal>")
249     ((eql :id) (format nil "<identifier~@[ `~A'~]>" token-value))
250     (keyword (format nil "`~(~A~)'" token-type))
251     (character (format nil "~:[<~:C>~;`~C'~]"
252                        (and (graphic-char-p token-type)
253                             (char/= token-type #\space))
254                        token-type))))
255
256 (defmethod scan-token ((lexer sod-lexer))
257   (with-slots (stream char keywords) lexer
258     (prog ((ch char))
259
260      consider
261        (cond
262
263          ;; End-of-file brings its own peculiar joy.
264          ((null ch) (return (values :eof t)))
265
266          ;; Ignore whitespace and continue around for more.
267          ((whitespace-char-p ch) (go scan))
268
269          ;; Strings.
270          ((or (char= ch #\") (char= ch #\'))
271           (with-default-error-location ((file-location lexer))
272             (let* ((quote ch)
273                    (string
274                     (with-output-to-string (out)
275                       (loop
276                         (flet ((getch ()
277                                  (setf ch (next-char lexer))
278                                  (when (null ch)
279                                    (cerror*
280                        "Unexpected end of file in string/character constant")
281                                    (return))))
282                           (getch)
283                           (cond ((char= ch quote) (return))
284                                 ((char= ch #\\) (getch)))
285                           (write-char ch out))))))
286               (setf ch (next-char lexer))
287               (ecase quote
288                 (#\" (return (values :string string)))
289                 (#\' (case (length string)
290                        (0 (cerror* "Empty character constant")
291                         (return (values :char #\?)))
292                        (1 (return (values :char (char string 0))))
293                        (t (cerror*
294                                  "Multiple characters in character constant")
295                           (return (values :char (char string 0))))))))))
296
297          ;; Pick out identifiers and keywords.
298          ((or (alpha-char-p ch) (char= ch #\_))
299
300           ;; Scan a sequence of alphanumerics and underscores.  We could
301           ;; allow more interesting identifiers, but it would damage our C
302           ;; lexical compatibility.
303           (let ((id (with-output-to-string (out)
304                       (loop
305                         (write-char ch out)
306                         (setf ch (next-char lexer))
307                         (when (or (null ch)
308                                   (not (or (alphanumericp ch)
309                                            (char= ch #\_))))
310                           (return))))))
311
312             ;; Done.
313             (return (values :id id))))
314
315          ;; Pick out numbers.  Currently only integers, but we support
316          ;; multiple bases.
317          ((digit-char-p ch)
318
319           ;; Sort out the prefix.  If we're looking at `0b', `0o' or `0x'
320           ;; (maybe uppercase) then we've got a funny radix to deal with.
321           ;; Otherwise, a leading zero signifies octal (daft, I know), else
322           ;; we're left with decimal.
323           (multiple-value-bind (radix skip-char)
324               (if (char/= ch #\0)
325                   (values 10 nil)
326                   (case (and (setf ch (next-char lexer))
327                              (char-downcase ch))
328                     (#\b (values 2 t))
329                     (#\o (values 8 t))
330                     (#\x (values 16 t))
331                     (t (values 8 nil))))
332
333             ;; If we last munched an interesting letter, we need to skip over
334             ;; it.  That's what the SKIP-CHAR flag is for.
335             ;;
336             ;; Danger, Will Robinson!  If we're' just about to eat a radix
337             ;; letter, then the next thing must be a digit.  For example,
338             ;; `0xfatenning' parses as a hex number followed by an identifier
339             ;; `0xfa ttening', but `0xturning' is an octal number followed
340             ;; by an identifier `0 xturning'.
341             (when skip-char
342               (let ((peek (next-char lexer)))
343                 (unless (digit-char-p peek radix)
344                   (pushback-char lexer ch)
345                   (return-from scan-token (values :integer 0)))
346                 (setf ch peek)))
347
348             ;; Scan an integer.  While there are digits, feed them into the
349             ;; accumulator.
350             (do ((accum 0 (+ (* accum radix) digit))
351                  (digit (and ch (digit-char-p ch radix))
352                         (and ch (digit-char-p ch radix))))
353                 ((null digit) (return-from scan-token
354                                 (values :integer accum)))
355               (setf ch (next-char lexer)))))
356
357          ;; A slash might be the start of a comment.
358          ((char= ch #\/)
359           (setf ch (next-char lexer))
360           (case ch
361
362             ;; Comment up to the end of the line.
363             (#\/
364              (loop
365                (setf ch (next-char lexer))
366                (when (or (null ch) (char= ch #\newline))
367                  (go scan))))
368
369             ;; Comment up to the next `*/'.
370             (#\*
371              (tagbody
372               top
373                 (case (setf ch (next-char lexer))
374                   (#\* (go star))
375                   ((nil) (go done))
376                   (t (go top)))
377               star
378                 (case (setf ch (next-char lexer))
379                   (#\* (go star))
380                   (#\/ (setf ch (next-char lexer))
381                        (go done))
382                   ((nil) (go done))
383                   (t (go top)))
384               done)
385              (go consider))
386
387             ;; False alarm.  (The next character is already set up.)
388             (t
389              (return (values #\/ t)))))
390
391          ;; A dot: might be `...'.  Tread carefully!  We need more lookahead
392          ;; than is good for us.
393          ((char= ch #\.)
394           (setf ch (next-char lexer))
395           (cond ((eql ch #\.)
396                  (setf ch (next-char lexer))
397                  (cond ((eql ch #\.) (return (values :ellpisis nil)))
398                        (t (pushback-char lexer #\.)
399                           (return (values #\. t)))))
400                 (t
401                  (return (values #\. t)))))
402
403          ;; Anything else is a lone delimiter.
404          (t
405           (return (multiple-value-prog1
406                       (values ch t)
407                     (next-char lexer)))))
408
409      scan
410        ;; Scan a new character and try again.
411        (setf ch (next-char lexer))
412        (go consider))))
413
414 ;;;--------------------------------------------------------------------------
415 ;;; C fragments.
416
417 (defclass c-fragment ()
418   ((location :initarg :location :type file-location
419              :accessor c-fragment-location)
420    (text :initarg :text :type string :accessor c-fragment-text))
421   (:documentation
422    "Represents a fragment of C code to be written to an output file.
423
424    A C fragment is aware of its original location, and will bear proper #line
425    markers when written out."))
426
427 (defun output-c-excursion (stream location thunk)
428   "Invoke THUNK surrounding it by writing #line markers to STREAM.
429
430    The first marker describes LOCATION; the second refers to the actual
431    output position in STREAM.  If LOCATION doesn't provide a line number then
432    no markers are output after all.  If the output stream isn't
433    position-aware then no final marker is output."
434
435   (let* ((location (file-location location))
436          (line (file-location-line location))
437          (pathname (file-location-pathname location))
438          (namestring (and pathname (namestring pathname))))
439     (cond (line
440            (format stream "~&#line ~D~@[ ~S~]~%" line namestring)
441            (funcall thunk)
442            (when (typep stream 'position-aware-stream)
443              (fresh-line stream)
444              (format stream "~&#line ~D ~S~%"
445                      (1+ (position-aware-stream-line stream))
446                      (namestring (stream-pathname stream)))))
447           (t
448            (funcall thunk)))))
449
450 (defmethod print-object ((fragment c-fragment) stream)
451   (let ((text (c-fragment-text fragment))
452         (location (c-fragment-location fragment)))
453     (if *print-escape*
454         (print-unreadable-object (fragment stream :type t)
455           (when location
456             (format stream "~A " location))
457           (cond ((< (length text) 40)
458                  (prin1 text stream) stream)
459                 (t
460                  (prin1 (subseq text 0 40) stream)
461                  (write-string "..." stream))))
462         (output-c-excursion stream location
463                             (lambda () (write-string text stream))))))
464
465 (defmethod make-load-form ((fragment c-fragment) &optional environment)
466   (make-load-form-saving-slots fragment :environment environment))
467
468 (defun scan-c-fragment (lexer end-chars)
469   "Snarfs a sequence of C tokens with balanced brackets.
470
471    Reads and consumes characters from the LEXER's stream, and returns them as
472    a string.  The string will contain whole C tokens, up as far as an
473    occurrence of one of the END-CHARS (a list) which (a) is not within a
474    string or character literal or comment, and (b) appears at the outer level
475    of nesting of brackets (whether round, curly or square -- again counting
476    only brackets which aren't themselves within string/character literals or
477    comments.  The final END-CHAR is not consumed.
478
479    An error is signalled if either the stream ends before an occurrence of
480    one of the END-CHARS, or if mismatching brackets are encountered.  No
481    other attempt is made to ensure that the characters read are in fact a
482    valid C fragment.
483
484    Both original /*...*/ and new //... comments are recognized.  Trigraphs
485    and digraphs are currently not recognized."
486
487   (let ((output (make-string-output-stream))
488         (ch (lexer-char lexer))
489         (start-floc (file-location lexer))
490         (delim nil)
491         (stack nil))
492
493     ;; Main loop.  At the top of this loop, we've already read a
494     ;; character into CH.  This is usually read at the end of processing
495     ;; the individual character, though sometimes (following `/', for
496     ;; example) it's read speculatively because we need one-character
497     ;; lookahead.
498     (block loop
499       (labels ((getch ()
500                  "Read the next character into CH; complain if we hit EOF."
501                  (unless (setf ch (next-char lexer))
502                    (cerror*-with-location start-floc
503                                       "Unexpected end-of-file in C fragment")
504                    (return-from loop))
505                  ch)
506                (putch ()
507                  "Write the character to the output buffer."
508                  (write-char ch output))
509                (push-delim (d)
510                  "Push a closing delimiter onto the stack."
511                  (push delim stack)
512                  (setf delim d)
513                  (getch)))
514
515         ;; Hack: if the first character is a newline, discard it.  Otherwise
516         ;; (a) the output fragment will look funny, and (b) the location
517         ;; information will be wrong.
518         (when (eql ch #\newline)
519           (getch))
520
521         ;; And fetch characters.
522         (loop
523
524           ;; Here we're outside any string or character literal, though we
525           ;; may be nested within brackets.  So, if there's no delimiter, and
526           ;; we've found the end character, we're done.
527           (when (and (null delim) (member ch end-chars))
528             (return))
529
530           ;; Otherwise take a copy of the character, and work out what to do
531           ;; next.
532           (putch)
533           (case ch
534
535             ;; Starting a literal.  Continue until we find a matching
536             ;; character not preceded by a `\'.
537             ((#\" #\')
538              (let ((quote ch))
539                (loop
540                  (getch)
541                  (putch)
542                  (when (eql ch quote)
543                    (return))
544                  (when (eql ch #\\)
545                    (getch)
546                    (putch)))
547                (getch)))
548
549             ;; Various kinds of opening bracket.  Stash the current
550             ;; delimiter, and note that we're looking for a new one.
551             (#\( (push-delim #\)))
552             (#\[ (push-delim #\]))
553             (#\{ (push-delim #\}))
554
555             ;; Various kinds of closing bracket.  If it matches the current
556             ;; delimeter then unstack the next one along.  Otherwise
557             ;; something's gone wrong: C syntax doesn't allow unmatched
558             ;; brackets.
559             ((#\) #\] #\})
560              (if (eql ch delim)
561                  (setf delim (pop stack))
562                  (cerror* "Unmatched `~C'." ch))
563              (getch))
564
565             ;; A slash.  Maybe a comment next.  But maybe not...
566             (#\/
567
568              ;; Examine the next character to find out how to proceed.
569              (getch)
570              (case ch
571
572                ;; A second slash -- eat until the end of the line.
573                (#\/
574                 (putch)
575                 (loop
576                   (getch)
577                   (putch)
578                   (when (eql ch #\newline)
579                     (return)))
580                 (getch))
581
582                ;; A star -- eat until we find a star-slash.  Since the star
583                ;; might be preceded by another star, we use a little state
584                ;; machine.
585                (#\*
586                 (putch)
587                 (tagbody
588
589                  main
590                    ;; Main state.  If we read a star, switch to star state;
591                    ;; otherwise eat the character and try again.
592                    (getch)
593                    (putch)
594                    (case ch
595                      (#\* (go star))
596                      (t (go main)))
597
598                  star
599                    ;; Star state.  If we read a slash, we're done; if we read
600                    ;; another star, stay in star state; otherwise go back to
601                    ;; main.
602                    (getch)
603                    (putch)
604                    (case ch
605                      (#\* (go star))
606                      (#\/ (go done))
607                      (t (go main)))
608
609                  done
610                    (getch)))))
611
612             ;; Something else.  Eat it and continue.
613             (t (getch)))))
614
615       (let* ((string (get-output-stream-string output))
616              (end (position-if (lambda (char)
617                                  (or (char= char #\newline)
618                                      (not (whitespace-char-p char))))
619                                string
620                                :from-end t))
621              (trimmed (if end
622                           (subseq string 0 (1+ end))
623                           "")))
624
625         ;; Return the fragment we've collected.
626         (make-instance 'c-fragment
627                        :location start-floc
628                        :text trimmed)))))
629
630 (defun c-fragment-reader (stream char arg)
631   "Reader for C-fragment syntax #{ ... stuff ... }."
632   (declare (ignore char arg))
633   (let ((lexer (make-instance 'sod-lexer
634                               :stream stream)))
635     (next-char lexer)
636     (scan-c-fragment lexer '(#\}))))
637
638 #+interactive
639 (set-dispatch-macro-character #\# #\{ 'c-fragment-reader)
640
641 ;;;--------------------------------------------------------------------------
642 ;;; Testing cruft.
643
644 #+test
645 (with-input-from-string (in "
646 { foo } 'x' /?/***/!
647 123 0432 0b010123 0xc0ffee __burp_32 class
648
649 0xturning 0xfattening
650 ...
651
652 class integer : integral_domain {
653   something here;
654 }
655
656 ")
657   (let* ((stream (make-instance 'position-aware-input-stream
658                                                      :stream in
659                                                      :file #p"magic"))
660          (lexer (make-instance 'sod-lexer
661                                :stream stream
662                                :keywords *sod-keywords*))
663          (list nil))
664     (next-char lexer)
665     (loop
666       (multiple-value-bind (tokty tokval) (next-token lexer)
667         (push (list tokty tokval) list)
668         (when (eql tokty :eof)
669           (return))))
670     (nreverse list)))
671
672 ;;;----- That's all, folks --------------------------------------------------