]> code.delx.au - gnu-emacs/blobdiff - lisp/progmodes/cc-engine.el
Update copyright year to 2014 by running admin/update-copyright.
[gnu-emacs] / lisp / progmodes / cc-engine.el
index 9077bdbb51399fa341649ed52ab8dee349f4bdbd..16d5da5f12c18313ff9f3ffd5da1135faeb44b16 100644 (file)
@@ -1,6 +1,6 @@
 ;;; cc-engine.el --- core syntax guessing engine for CC mode -*- coding: utf-8 -*-
 
-;; Copyright (C) 1985, 1987, 1992-2013 Free Software Foundation, Inc.
+;; Copyright (C) 1985, 1987, 1992-2014 Free Software Foundation, Inc.
 
 ;; Authors:    2001- Alan Mackenzie
 ;;             1998- Martin Stjernholm
@@ -1135,9 +1135,13 @@ comment at the start of cc-engine.el for more info."
                   (not (memq sym '(boundary ignore nil))))
          ;; Need to investigate closer whether we've crossed
          ;; between a substatement and its containing statement.
-         (if (setq saved (if (looking-at c-block-stmt-1-key)
-                             ptok
-                           pptok))
+         (if (setq saved
+                   (cond ((and (looking-at c-block-stmt-1-2-key)
+                               (eq (char-after ptok) ?\())
+                          pptok)
+                         ((looking-at c-block-stmt-1-key)
+                          ptok)
+                         (t pptok)))
              (cond ((> start saved) (setq pos saved))
                    ((= start saved) (setq ret 'up)))))
 
@@ -1257,16 +1261,22 @@ comment at the start of cc-engine.el for more info."
              ;; looking for more : and ?.
              (setq c-maybe-labelp nil
                    skip-chars (substring c-stmt-delim-chars 0 -2)))
-            ;; At a CPP construct?
-            ((and c-opt-cpp-symbol (looking-at c-opt-cpp-symbol)
-                  (save-excursion
-                    (forward-line 0)
-                    (looking-at c-opt-cpp-prefix)))
-             (c-end-of-macro))
+            ;; At a CPP construct or a "#" or "##" operator?
+            ((and c-opt-cpp-symbol (looking-at c-opt-cpp-symbol))
+             (if (save-excursion
+                   (skip-chars-backward " \t")
+                   (and (bolp)
+                        (or (bobp)
+                            (not (eq (char-before (1- (point))) ?\\)))))
+                 (c-end-of-macro)
+               (skip-chars-forward c-opt-cpp-symbol)))
             ((memq (char-after) non-skip-list)
              (throw 'done (point)))))
          ;; In trailing space after an as yet undetected virtual semicolon?
          (c-backward-syntactic-ws from)
+         (when (and (bolp) (not (bobp))) ; Can happen in AWK Mode with an
+                                         ; unterminated string/regexp.
+           (backward-char))
          (if (and (< (point) to)
                   (c-at-vsemi-p))
              (point)
@@ -4722,6 +4732,11 @@ comment at the start of cc-engine.el for more info."
   ;; inside `c-find-decl-spots'.  The point is left at `cfd-match-pos'
   ;; if there is a match, otherwise at `cfd-limit'.
   ;;
+  ;; The macro moves point forward to the next putative start of a declaration
+  ;; or cfd-limit.  This decl start is the next token after a "declaration
+  ;; prefix".  The declaration prefix is the earlier of `cfd-prop-match' and
+  ;; `cfd-re-match'.  `cfd-match-pos' is set to the decl prefix.
+  ;;
   ;; This macro might do hidden buffer changes.
 
   '(progn
@@ -4743,34 +4758,47 @@ comment at the start of cc-engine.el for more info."
        (if (> cfd-re-match-end (point))
           (goto-char cfd-re-match-end))
 
-       (while (if (setq cfd-re-match-end
-                       (re-search-forward c-decl-prefix-or-start-re
-                                          cfd-limit 'move))
-
-                 ;; Match.  Check if it's inside a comment or string literal.
-                 (c-got-face-at
-                  (if (setq cfd-re-match (match-end 1))
-                      ;; Matched the end of a token preceding a decl spot.
-                      (progn
-                        (goto-char cfd-re-match)
-                        (1- cfd-re-match))
-                    ;; Matched a token that start a decl spot.
-                    (goto-char (match-beginning 0))
-                    (point))
-                  c-literal-faces)
-
-               ;; No match.  Finish up and exit the loop.
-               (setq cfd-re-match cfd-limit)
-               nil)
-
-        ;; Skip out of comments and string literals.
-        (while (progn
-                 (goto-char (next-single-property-change
-                             (point) 'face nil cfd-limit))
-                 (and (< (point) cfd-limit)
-                      (c-got-face-at (point) c-literal-faces)))))
+       ;; Each time round, the next `while' moves forward over a pseudo match
+       ;; of `c-decl-prefix-or-start-re' which is either inside a literal, or
+       ;; is a ":" not preceded by "public", etc..  `cfd-re-match' and
+       ;; `cfd-re-match-end' get set.
+       (while
+          (progn
+            (setq cfd-re-match-end (re-search-forward c-decl-prefix-or-start-re
+                                                      cfd-limit 'move))
+            (cond
+             ((null cfd-re-match-end)
+              ;; No match.  Finish up and exit the loop.
+              (setq cfd-re-match cfd-limit)
+              nil)
+             ((c-got-face-at
+               (if (setq cfd-re-match (match-end 1))
+                   ;; Matched the end of a token preceding a decl spot.
+                   (progn
+                     (goto-char cfd-re-match)
+                     (1- cfd-re-match))
+                 ;; Matched a token that start a decl spot.
+                 (goto-char (match-beginning 0))
+                 (point))
+               c-literal-faces)
+              ;; Pseudo match inside a comment or string literal.  Skip out
+              ;; of comments and string literals.
+              (while (progn
+                       (goto-char (next-single-property-change
+                                   (point) 'face nil cfd-limit))
+                       (and (< (point) cfd-limit)
+                            (c-got-face-at (point) c-literal-faces))))
+              t)                     ; Continue the loop over pseudo matches.
+             ((and (match-string 1)
+                   (string= (match-string 1) ":")
+                   (save-excursion
+                     (or (/= (c-backward-token-2 2) 0) ; no search limit.  :-(
+                         (not (looking-at c-decl-start-colon-kwd-re)))))
+              ;; Found a ":" which isn't part of "public:", etc.
+              t)
+             (t nil)))) ;; Found a real match.  Exit the pseudo-match loop.
 
-       ;; If we matched at the decl start, we have to back up over the
+       ;; If our match was at the decl start, we have to back up over the
        ;; preceding syntactic ws to set `cfd-match-pos' and to catch
        ;; any decl spots in the syntactic ws.
        (unless cfd-re-match
@@ -6472,6 +6500,15 @@ comment at the start of cc-engine.el for more info."
           (c-go-list-forward)
          t)))
 
+(defmacro c-pull-open-brace (ps)
+  ;; Pull the next open brace from PS (which has the form of paren-state),
+  ;; skipping over any brace pairs.  Returns NIL when PS is exhausted.
+  `(progn
+     (while (consp (car ,ps))
+       (setq ,ps (cdr ,ps)))
+     (prog1 (car ,ps)
+       (setq ,ps (cdr ,ps)))))
+
 (defun c-back-over-member-initializers ()
   ;; Test whether we are in a C++ member initializer list, and if so, go back
   ;; to the introducing ":", returning the position of the opening paren of
@@ -6883,45 +6920,57 @@ comment at the start of cc-engine.el for more info."
          ;; can happen since we don't know if
          ;; `c-restricted-<>-arglists' will be correct inside the
          ;; arglist paren that gets entered.
-         c-parse-and-markup-<>-arglists)
+         c-parse-and-markup-<>-arglists
+         ;; Start of the identifier for which `got-identifier' was set.
+         name-start)
 
       (goto-char id-start)
 
       ;; Skip over type decl prefix operators.  (Note similar code in
       ;; `c-font-lock-declarators'.)
-      (while (and (looking-at c-type-decl-prefix-key)
-                 (if (and (c-major-mode-is 'c++-mode)
-                          (match-beginning 3))
-                     ;; If the second submatch matches in C++ then
-                     ;; we're looking at an identifier that's a
-                     ;; prefix only if it specifies a member pointer.
-                     (when (setq got-identifier (c-forward-name))
-                       (if (looking-at "\\(::\\)")
-                           ;; We only check for a trailing "::" and
-                           ;; let the "*" that should follow be
-                           ;; matched in the next round.
-                           (progn (setq got-identifier nil) t)
-                         ;; It turned out to be the real identifier,
-                         ;; so stop.
-                         nil))
-                   t))
-
-       (if (eq (char-after) ?\()
+      (if (and c-recognize-typeless-decls
+              (equal c-type-decl-prefix-key "\\<\\>"))
+         (when (eq (char-after) ?\()
            (progn
              (setq paren-depth (1+ paren-depth))
-             (forward-char))
-         (unless got-prefix-before-parens
-           (setq got-prefix-before-parens (= paren-depth 0)))
-         (setq got-prefix t)
-         (goto-char (match-end 1)))
-       (c-forward-syntactic-ws))
+             (forward-char)))
+       (while (and (looking-at c-type-decl-prefix-key)
+                   (if (and (c-major-mode-is 'c++-mode)
+                            (match-beginning 3))
+                       ;; If the third submatch matches in C++ then
+                       ;; we're looking at an identifier that's a
+                       ;; prefix only if it specifies a member pointer.
+                       (when (progn (setq pos (point))
+                                    (setq got-identifier (c-forward-name)))
+                         (setq name-start pos)
+                         (if (looking-at "\\(::\\)")
+                             ;; We only check for a trailing "::" and
+                             ;; let the "*" that should follow be
+                             ;; matched in the next round.
+                             (progn (setq got-identifier nil) t)
+                           ;; It turned out to be the real identifier,
+                           ;; so stop.
+                           nil))
+                     t))
+
+         (if (eq (char-after) ?\()
+             (progn
+               (setq paren-depth (1+ paren-depth))
+               (forward-char))
+           (unless got-prefix-before-parens
+             (setq got-prefix-before-parens (= paren-depth 0)))
+           (setq got-prefix t)
+           (goto-char (match-end 1)))
+         (c-forward-syntactic-ws)))
 
       (setq got-parens (> paren-depth 0))
 
       ;; Skip over an identifier.
       (or got-identifier
          (and (looking-at c-identifier-start)
-              (setq got-identifier (c-forward-name))))
+              (setq pos (point))
+              (setq got-identifier (c-forward-name))
+              (setq name-start pos)))
 
       ;; Skip over type decl suffix operators.
       (while (if (looking-at c-type-decl-suffix-key)
@@ -7012,23 +7061,27 @@ comment at the start of cc-engine.el for more info."
                ;; declaration.
                (throw 'at-decl-or-cast t))
 
-             (when (and got-parens
-                        (not got-prefix)
-                        (not got-suffix-after-parens)
-                        (or backup-at-type
-                            maybe-typeless
-                            backup-maybe-typeless))
-               ;; Got a declaration of the form "foo bar (gnu);" where we've
-               ;; recognized "bar" as the type and "gnu" as the declarator.
-               ;; In this case it's however more likely that "bar" is the
-               ;; declarator and "gnu" a function argument or initializer (if
-               ;; `c-recognize-paren-inits' is set), since the parens around
-               ;; "gnu" would be superfluous if it's a declarator.  Shift the
-               ;; type one step backward.
-               (c-fdoc-shift-type-backward)))
-
-         ;; Found no identifier.
 
+              (when (and got-parens
+                         (not got-prefix)
+                         ;; (not got-suffix-after-parens)
+                         (or backup-at-type
+                             maybe-typeless
+                             backup-maybe-typeless
+                             (eq at-decl-or-cast t)
+                             (save-excursion
+                               (goto-char name-start)
+                               (not (memq (c-forward-type) '(nil maybe))))))
+                ;; Got a declaration of the form "foo bar (gnu);" or "bar
+                ;; (gnu);" where we've recognized "bar" as the type and "gnu"
+                ;; as the declarator.  In this case it's however more likely
+                ;; that "bar" is the declarator and "gnu" a function argument
+                ;; or initializer (if `c-recognize-paren-inits' is set),
+                ;; since the parens around "gnu" would be superfluous if it's
+                ;; a declarator.  Shift the type one step backward.
+                (c-fdoc-shift-type-backward)))
+
+          ;; Found no identifier.
          (if backup-at-type
              (progn
 
@@ -7193,19 +7246,23 @@ comment at the start of cc-engine.el for more info."
        ;; uncommon (e.g. some placements of "const" in C++) it's not worth
        ;; the effort to look for them.)
 
-       (unless (or at-decl-end (looking-at "=[^=]"))
-         ;; If this is a declaration it should end here or its initializer(*)
-         ;; should start here, so check for allowed separation tokens.  Note
-         ;; that this rule doesn't work e.g. with a K&R arglist after a
-         ;; function header.
-         ;;
-         ;; *) Don't check for C++ style initializers using parens
-         ;; since those already have been matched as suffixes.
-         ;;
-         ;; If `at-decl-or-cast' is then we've found some other sign that
-         ;; it's a declaration or cast, so then it's probably an
-         ;; invalid/unfinished one.
-         (throw 'at-decl-or-cast at-decl-or-cast))
+;;; 2008-04-16: commented out the next form, to allow the function to recognize
+;;; "foo (int bar)" in CC (an implicit type (in class foo) without a semicolon)
+;;; as a(n almost complete) declaration, enabling it to be fontified.
+       ;; CASE 13
+       ;; (unless (or at-decl-end (looking-at "=[^=]"))
+       ;; If this is a declaration it should end here or its initializer(*)
+       ;; should start here, so check for allowed separation tokens.  Note
+       ;; that this rule doesn't work e.g. with a K&R arglist after a
+       ;; function header.
+       ;;
+       ;; *) Don't check for C++ style initializers using parens
+       ;; since those already have been matched as suffixes.
+       ;;
+       ;; If `at-decl-or-cast' is then we've found some other sign that
+       ;; it's a declaration or cast, so then it's probably an
+       ;; invalid/unfinished one.
+       ;;  (throw 'at-decl-or-cast at-decl-or-cast))
 
        ;; Below are tests that only should be applied when we're certain to
        ;; not have parsed halfway through an expression.
@@ -7382,7 +7439,11 @@ comment at the start of cc-engine.el for more info."
        ;; interactive refontification.
        (c-put-c-type-property (point) 'c-decl-arg-start))
 
-      (when (and c-record-type-identifiers at-type (not (eq at-type t)))
+      (when (and c-record-type-identifiers at-type ;; (not (eq at-type t))
+                ;; There seems no reason to exclude a token from
+                ;; fontification just because it's "a known type that can't
+                ;; be a name or other expression".  2013-09-18.
+                )
        (let ((c-promote-possible-types t))
          (save-excursion
            (goto-char type-start)
@@ -7984,7 +8045,8 @@ comment at the start of cc-engine.el for more info."
         (or (looking-at c-block-stmt-1-key)
             (and (eq (char-after) ?\()
                  (zerop (c-backward-token-2 1 t lim))
-                 (looking-at c-block-stmt-2-key)))
+                 (or (looking-at c-block-stmt-2-key)
+                     (looking-at c-block-stmt-1-2-key))))
         (point))))
 
 (defun c-after-special-operator-id (&optional lim)
@@ -8391,15 +8453,6 @@ comment at the start of cc-engine.el for more info."
          (back-to-indentation)
          (vector (point) open-paren-pos))))))
 
-(defmacro c-pull-open-brace (ps)
-  ;; Pull the next open brace from PS (which has the form of paren-state),
-  ;; skipping over any brace pairs.  Returns NIL when PS is exhausted.
-  `(progn
-     (while (consp (car ,ps))
-       (setq ,ps (cdr ,ps)))
-     (prog1 (car ,ps)
-       (setq ,ps (cdr ,ps)))))
-
 (defun c-most-enclosing-decl-block (paren-state)
   ;; Return the buffer position of the most enclosing decl-block brace (in the
   ;; sense of c-looking-at-decl-block) in the PAREN-STATE structure, or nil if
@@ -8431,6 +8484,34 @@ comment at the start of cc-engine.el for more info."
                      (not (looking-at "=")))))
       b-pos)))
 
+(defun c-backward-over-enum-header ()
+  ;; We're at a "{".  Move back to the enum-like keyword that starts this
+  ;; declaration and return t, otherwise don't move and return nil.
+  (let ((here (point))
+       up-sexp-pos before-identifier)
+    (while
+       (and
+        (eq (c-backward-token-2) 0)
+        (or (not (looking-at "\\s)"))
+            (c-go-up-list-backward))
+        (cond
+         ((and (looking-at c-symbol-key) (c-on-identifier)
+               (not before-identifier))
+          (setq before-identifier t))
+         ((and before-identifier
+               (or (eq (char-after) ?,)
+                   (looking-at c-postfix-decl-spec-key)))
+          (setq before-identifier nil)
+          t)
+         ((looking-at c-brace-list-key) nil)
+         ((and c-recognize-<>-arglists
+               (eq (char-after) ?<)
+               (looking-at "\\s("))
+          t)
+         (t nil))))
+    (or (looking-at c-brace-list-key)
+       (progn (goto-char here) nil))))
+
 (defun c-inside-bracelist-p (containing-sexp paren-state)
   ;; return the buffer position of the beginning of the brace list
   ;; statement if we're inside a brace list, otherwise return nil.
@@ -8445,18 +8526,9 @@ comment at the start of cc-engine.el for more info."
   ;; This function might do hidden buffer changes.
   (or
    ;; This will pick up brace list declarations.
-   (c-safe
-    (save-excursion
-      (goto-char containing-sexp)
-      (c-forward-sexp -1)
-      (let (bracepos)
-       (if (and (or (looking-at c-brace-list-key)
-                    (progn (c-forward-sexp -1)
-                           (looking-at c-brace-list-key)))
-                (setq bracepos (c-down-list-forward (point)))
-                (not (c-crosses-statement-barrier-p (point)
-                                                    (- bracepos 2))))
-           (point)))))
+   (save-excursion
+     (goto-char containing-sexp)
+     (c-backward-over-enum-header))
    ;; this will pick up array/aggregate init lists, even if they are nested.
    (save-excursion
      (let ((class-key
@@ -8464,10 +8536,10 @@ comment at the start of cc-engine.el for more info."
            ;; check for the class key here.
            (and (c-major-mode-is 'pike-mode)
                 c-decl-block-key))
-          bufpos braceassignp lim next-containing)
+          bufpos braceassignp lim next-containing macro-start)
        (while (and (not bufpos)
                   containing-sexp)
-          (when paren-state
+        (when paren-state
             (if (consp (car paren-state))
                 (setq lim (cdr (car paren-state))
                       paren-state (cdr paren-state))
@@ -8548,22 +8620,38 @@ comment at the start of cc-engine.el for more info."
                                          ))))
                                nil)
                               (t t))))))
-              (if (and (eq braceassignp 'dontknow)
-                       (/= (c-backward-token-2 1 t lim) 0))
-                  (setq braceassignp nil)))
-            (if (not braceassignp)
-                (if (eq (char-after) ?\;)
-                    ;; Brace lists can't contain a semicolon, so we're done.
-                    (setq containing-sexp nil)
-                  ;; Go up one level.
-                  (setq containing-sexp next-containing
-                        lim nil
-                        next-containing nil))
-              ;; we've hit the beginning of the aggregate list
-              (c-beginning-of-statement-1
-               (c-most-enclosing-brace paren-state))
-              (setq bufpos (point))))
-          )
+            (if (and (eq braceassignp 'dontknow)
+                     (/= (c-backward-token-2 1 t lim) 0))
+                (setq braceassignp nil)))
+          (cond
+           (braceassignp
+            ;; We've hit the beginning of the aggregate list.
+            (c-beginning-of-statement-1
+             (c-most-enclosing-brace paren-state))
+            (setq bufpos (point)))
+           ((eq (char-after) ?\;)
+            ;; Brace lists can't contain a semicolon, so we're done.
+            (setq containing-sexp nil))
+           ((and (setq macro-start (point))
+                 (c-forward-to-cpp-define-body)
+                 (eq (point) containing-sexp))
+            ;; We've a macro whose expansion starts with the '{'.
+            ;; Heuristically, if we have a ';' in it we've not got a
+            ;; brace list, otherwise we have.
+            (let ((macro-end (progn (c-end-of-macro) (point))))
+              (goto-char containing-sexp)
+              (forward-char)
+              (if (and (c-syntactic-re-search-forward "[;,]" macro-end t t)
+                       (eq (char-before) ?\;))
+                  (setq bufpos nil
+                        containing-sexp nil)
+                (setq bufpos macro-start))))
+           (t
+            ;; Go up one level
+            (setq containing-sexp next-containing
+                  lim nil
+                  next-containing nil)))))
+
        bufpos))
    ))
 
@@ -9787,12 +9875,12 @@ comment at the start of cc-engine.el for more info."
                              (not (eq (char-after) ?:))
                              )))
                   (save-excursion
-                    (c-backward-syntactic-ws lim)
-                    (if (eq char-before-ip ?:)
-                        (progn
-                          (forward-char -1)
-                          (c-backward-syntactic-ws lim)))
-                    (back-to-indentation)
+                    (c-beginning-of-statement-1 lim)
+                    (when (looking-at c-opt-<>-sexp-key)
+                      (goto-char (match-end 1))
+                      (c-forward-syntactic-ws)
+                      (c-forward-<>-arglist nil)
+                      (c-forward-syntactic-ws))
                     (looking-at c-class-key)))
              ;; for Java
              (and (c-major-mode-is 'java-mode)