]> code.delx.au - gnu-emacs/blobdiff - lisp/progmodes/fortran.el
Merge from emacs--devo--0
[gnu-emacs] / lisp / progmodes / fortran.el
index 5badcfb1efad8290b59511f217c0f382669963bf..b9865613765275c0c206cdace977181c04ba4d22 100644 (file)
@@ -1,17 +1,17 @@
 ;;; fortran.el --- Fortran mode for GNU Emacs
 
-;; Copyright (c) 1986, 93, 94, 95, 97, 98, 99, 2000, 2001
-;;   Free Software Foundation, Inc.
+;; Copyright (C) 1986, 1993, 1994, 1995, 1997, 1998, 1999, 2000, 2001,
+;;               2002, 2003, 2004, 2005, 2006, 2007  Free Software Foundation, Inc.
 
 ;; Author: Michael D. Prange <prange@erl.mit.edu>
-;; Maintainer: Glenn Morris <gmorris@ast.cam.ac.uk>
+;; Maintainer: Glenn Morris <rgm@gnu.org>
 ;; Keywords: fortran, languages
 
 ;; This file is part of GNU Emacs.
 
 ;; GNU Emacs is free software; you can redistribute it and/or modify
 ;; it under the terms of the GNU General Public License as published by
-;; the Free Software Foundation; either version 2, or (at your option)
+;; the Free Software Foundation; either version 3, or (at your option)
 ;; any later version.
 
 ;; GNU Emacs is distributed in the hope that it will be useful,
@@ -21,8 +21,8 @@
 
 ;; You should have received a copy of the GNU General Public License
 ;; along with GNU Emacs; see the file COPYING.  If not, write to the
-;; Free Software Foundation, Inc., 59 Temple Place - Suite 330,
-;; Boston, MA 02111-1307, USA.
+;; Free Software Foundation, Inc., 51 Franklin Street, Fifth Floor,
+;; Boston, MA 02110-1301, USA.
 
 ;;; Commentary:
 
 ;;   second in column 6.
 ;; * Support any other extensions to f77 grokked by GNU Fortran I've missed.
 
-(eval-when-compile                     ; silence compiler
-  (defvar dabbrev-case-fold-search)
-  (defvar imenu-case-fold-search)
-  (defvar imenu-syntax-alist))
+;; silence compiler
+(defvar dabbrev-case-fold-search)
+(defvar font-lock-syntactic-keywords)
+(defvar gud-find-expr-function)
+(defvar imenu-case-fold-search)
+(defvar imenu-syntax-alist)
 
 
 (defgroup fortran nil
   "Major mode for editing fixed format Fortran code."
-  :link  '(custom-manual "(emacs)Fortran")
+  :link '(custom-group-link :tag "Font Lock Faces group" font-lock-faces)
+  :link '(custom-manual "(emacs)Fortran")
   :group 'languages)
 
 (defgroup fortran-indent nil
@@ -95,7 +98,7 @@ with a character in column 6."
   :group 'fortran-indent)
 
 (defcustom fortran-if-indent 3
-  "*Extra indentation applied to IF blocks."
+  "*Extra indentation applied to IF, SELECT CASE and WHERE blocks."
   :type  'integer
   :group 'fortran-indent)
 
@@ -147,7 +150,7 @@ You might want to change this to \"*\", for instance."
   "*Regexp to match a directive line.
 The matching text will be fontified with `font-lock-keyword-face'.
 The matching line will be given zero indentation."
-  :version "21.4"
+  :version "22.1"
   :type    'regexp
   :group   'fortran-indent)
 
@@ -237,10 +240,25 @@ See the variable `fortran-column-ruler-fixed' for fixed format mode."
 
 (defcustom fortran-break-before-delimiters t
   "*Non-nil causes filling to break lines before delimiters.
-Delimiters are whitespace, commas, quotes, and operators."
+Delimiters are characters matching the regexp `fortran-break-delimiters-re'."
   :type  'boolean
   :group 'fortran)
 
+(defconst fortran-break-delimiters-re "[-+*/><=, \t]"
+  "Regexp matching delimiter characters at which lines may be broken.
+There are certain tokens comprised entirely of characters
+matching this regexp that should not be split, and these are
+specified by the constant `fortran-no-break-re'.")
+
+;; The ">=", etc F77 extensions are supported by g77.
+(defconst fortran-no-break-re
+  (regexp-opt '("**" "//" "=>" ">=" "<=" "==" "/=") 'paren)
+  "Regexp specifying where not to break lines when filling.
+This regexp matches certain tokens comprised entirely of
+characters matching the regexp `fortran-break-delimiters-re' that should
+not be split by filling.  Each element is assumed to be two
+characters long.")
+
 (defcustom fortran-mode-hook nil
   "Hook run when entering Fortran mode."
   :type  'hook
@@ -306,7 +324,8 @@ program\\|subroutine\\)\\>[ \t]*\\(\\sw+\\)?"
                             "while" "inquire" "stop" "return"
                             "include" "open" "close" "read"
                             "write" "format" "print" "select" "case"
-                            "cycle" "exit" "rewind" "backspace")
+                            "cycle" "exit" "rewind" "backspace"
+                            "where" "elsewhere")
                           'paren) "\\>")
            ;; Builtin operators.
            (concat "\\." (regexp-opt
@@ -355,6 +374,29 @@ program\\|subroutine\\)\\>[ \t]*\\(\\sw+\\)?"
                 fortran-font-lock-keywords-2)))
   "Gaudy level highlighting for Fortran mode.")
 
+(defvar fortran-font-lock-keywords-4
+  (append fortran-font-lock-keywords-3
+          (list (list
+                 (concat "\\<"
+                         (regexp-opt
+                          '("int" "ifix" "idint" "real" "float" "sngl"
+                            "dble" "cmplx" "ichar" "char" "aint" "dint"
+                            "anint" "dnint" "nint" "idnint" "iabs" "abs"
+                            "dabs" "cabs" "mod" "amod" "dmod" "isign"
+                            "sign" "dsign" "idim" "dim" "ddim" "dprod"
+                            "max" "max0" "amax1" "dmax1" "amax0" "max1"
+                            "min" "min0" "amin1" "dmin1" "amin0" "min1"
+                            "len" "index" "lge" "lgt" "lle" "llt" "aimag"
+                            "conjg" "sqrt" "dsqrt" "csqrt" "exp" "dexp"
+                            "cexp" "log" "alog" "dlog" "clog" "log10"
+                            "alog10" "dlog10" "sin" "dsin" "csin" "cos"
+                            "dcos" "ccos" "tan" "dtan" "asin" "dasin"
+                            "acos" "dacos" "atan" "datan" "atan2" "datan2"
+                            "sinh" "dsinh" "cosh" "dcosh" "tanh" "dtanh")
+                          'paren) "[ \t]*(") '(1 font-lock-builtin-face))))
+  "Maximum highlighting for Fortran mode.
+Consists of level 3 plus all other intrinsics not already highlighted.")
+
 ;; Comments are real pain in Fortran because there is no way to
 ;; represent the standard comment syntax in an Emacs syntax table.
 ;; (We can do so for F90-style).  Therefore an unmatched quote in a
@@ -393,6 +435,64 @@ These get fixed-format comments fontified.")
    '(nil "^\\s-+\\(block\\s-*data\\)\\s-*$" 1))
   "Value for `imenu-generic-expression' in Fortran mode.")
 
+\f
+;; Hideshow support.
+(defconst fortran-blocks-re
+  (concat "block[ \t]*data\\|select[ \t]*case\\|"
+          (regexp-opt '("do" "if" "interface" "function" "map" "program"
+                        "structure" "subroutine" "union" "where")))
+  "Regexp potentially indicating the start or end of a Fortran \"block\".
+Omits naked END statements, and DO-loops closed by anything other
+than ENDDO.")
+
+(defconst fortran-end-block-re
+  ;; Do-loops terminated by things other than ENDDO cannot be handled
+  ;; with a regexp. This omission does not seem to matter to hideshow...
+  (concat "^[ \t0-9]*\\<end[ \t]*\\("
+          fortran-blocks-re
+          ;; Naked END statement.
+          "\\|!\\|$\\)")
+  "Regexp matching the end of a Fortran \"block\", from the line start.
+Note that only ENDDO is handled for the end of a DO-loop.  Used
+in the Fortran entry in `hs-special-modes-alist'.")
+
+(defconst fortran-start-block-re
+  (concat
+   "^[ \t0-9]*\\("                      ; statement number
+   ;; Structure label for DO, IF, SELECT, WHERE.
+   "\\(\\(\\sw+[ \t]*:[ \t]*\\)?"
+   ;; IF blocks are a nuisance:
+   ;; IF ( ... ) foo   is not a block, but a single statement.
+   ;; IF ( ... ) THEN  can be split over multiple lines.
+   ;; [So can, eg, a DO WHILE (... ), but that is less common, I hope.]
+   ;; The regexp below allows for it to be split over at most 2 lines.
+   ;; That leads to the problem of not matching two consecutive IF
+   ;; statements as one, eg:
+   ;; IF ( ... ) foo
+   ;; IF ( ... ) THEN
+   ;; It simply is not possible to do this in a 100% correct fashion
+   ;; using a regexp - see the functions fortran-end-if,
+   ;; fortran-beginning-if for the hoops we have to go through.
+   ;; An alternative is to match on THEN at a line end, eg:
+   ;;   ".*)[ \t]*then[ \t]*\\($\\|!\\)"
+   ;; This would also match ELSE branches, though. This does not seem
+   ;; right to me, because then one has neighbouring blocks that are
+   ;; not nested in each other.
+   "\\(if[ \t]*(\\(.*\\|"
+   ".*\n\\([^if]*\\([^i].\\|.[^f]\\|.\\>\\)\\)\\)\\<then\\|"
+   "do\\|select[ \t]*case\\|where\\)\\)\\|"
+   (regexp-opt '("interface" "function" "map" "program"
+                 "structure" "subroutine" "union"))
+   "\\|block[ \t]*data\\)[ \t]*")
+  "Regexp matching the start of a Fortran \"block\", from the line start.
+A simple regexp cannot do this in fully correct fashion, so this
+tries to strike a compromise between complexity and flexibility.
+Used in the Fortran entry in `hs-special-modes-alist'.")
+
+(add-to-list 'hs-special-modes-alist
+            `(fortran-mode ,fortran-start-block-re ,fortran-end-block-re
+                            "^[cC*!]" fortran-end-of-block nil))
+
 \f
 (defvar fortran-mode-syntax-table
   (let ((table (make-syntax-table)))
@@ -407,7 +507,8 @@ These get fixed-format comments fontified.")
     (modify-syntax-entry ?/  "."  table)
     (modify-syntax-entry ?\' "\"" table)
     (modify-syntax-entry ?\" "\"" table)
-    ;; Consistent with GNU Fortran -- see the manual.
+    ;; Consistent with GNU Fortran's default -- see the manual.
+    ;; The F77 standard imposes no rule on this issue.
     (modify-syntax-entry ?\\ "\\" table)
     ;; This might be better as punctuation, as for C, but this way you
     ;; can treat floating-point numbers as symbols.
@@ -419,12 +520,20 @@ These get fixed-format comments fontified.")
     table)
   "Syntax table used in Fortran mode.")
 
+(defvar fortran-gud-syntax-table
+  (let ((st (make-syntax-table fortran-mode-syntax-table)))
+    (modify-syntax-entry ?\n "." st)
+    st)
+  "Syntax table used to parse Fortran expressions for printing in GUD.")
+
 (defvar fortran-mode-map
   (let ((map (make-sparse-keymap)))
     (define-key map ";"        'fortran-abbrev-start)
     (define-key map "\C-c;"    'fortran-comment-region)
     (define-key map "\M-;"     'fortran-indent-comment)
     (define-key map "\M-\n"    'fortran-split-line)
+    (define-key map "\M-\C-n"  'fortran-end-of-block)
+    (define-key map "\M-\C-p"  'fortran-beginning-of-block)
     (define-key map "\M-\C-q"  'fortran-indent-subprogram)
     (define-key map "\C-c\C-w" 'fortran-window-create-momentarily)
     (define-key map "\C-c\C-r" 'fortran-column-ruler)
@@ -495,80 +604,82 @@ These get fixed-format comments fontified.")
 
 \f
 (defvar fortran-mode-abbrev-table
-  (let (abbrevs-changed)
+  (progn
     (define-abbrev-table 'fortran-mode-abbrev-table nil)
-    ;; Use the 6th arg (SYSTEM-FLAG) of define-abbrev if possible.
-    ;; Only use `apply' to quieten the byte-compiler.
-    (mapcar
-     (function (lambda (element)
-                 (condition-case nil
-                     (apply 'define-abbrev fortran-mode-abbrev-table
-                            (append element '(nil 0 t)))
-                   (wrong-number-of-arguments
-                    (apply 'define-abbrev fortran-mode-abbrev-table
-                           (append element '(nil 0)))))))
-     '((";au"   "automatic"         )
-       (";b"    "byte"              )
-       (";bd"   "block data"        )
-       (";ch"   "character"         )
-       (";cl"   "close"             )
-       (";c"    "continue"          )
-       (";cm"   "common"            )
-       (";cx"   "complex"           )
-       (";df"   "define"            )
-       (";di"   "dimension"         )
-       (";do"   "double"            )
-       (";dc"   "double complex"    )
-       (";dp"   "double precision"  )
-       (";dw"   "do while"          )
-       (";e"    "else"              )
-       (";ed"   "enddo"             )
-       (";el"   "elseif"            )
-       (";en"   "endif"             )
-       (";eq"   "equivalence"       )
-       (";ew"   "endwhere"          )
-       (";ex"   "external"          )
-       (";ey"   "entry"             )
-       (";f"    "format"            )
-       (";fa"   ".false."           )
-       (";fu"   "function"          )
-       (";g"    "goto"              )
-       (";im"   "implicit"          )
-       (";ib"   "implicit byte"     )
-       (";ic"   "implicit complex"  )
-       (";ich"  "implicit character")
-       (";ii"   "implicit integer"  )
-       (";il"   "implicit logical"  )
-       (";ir"   "implicit real"     )
-       (";inc"  "include"           )
-       (";in"   "integer"           )
-       (";intr" "intrinsic"         )
-       (";l"    "logical"           )
-       (";n"    "namelist"          )
-       (";o"    "open"              )   ; was ;op
-       (";pa"   "parameter"         )
-       (";pr"   "program"           )
-       (";ps"   "pause"             )
-       (";p"    "print"             )
-       (";rc"   "record"            )
-       (";re"   "real"              )
-       (";r"    "read"              )
-       (";rt"   "return"            )
-       (";rw"   "rewind"            )
-       (";s"    "stop"              )
-       (";sa"   "save"              )
-       (";st"   "structure"         )
-       (";sc"   "static"            )
-       (";su"   "subroutine"        )
-       (";tr"   ".true."            )
-       (";ty"   "type"              )
-       (";vo"   "volatile"          )
-       (";w"    "write"             )
-       (";wh"   "where"             )))
-    fortran-mode-abbrev-table))
+    fortran-mode-abbrev-table)
+  "Abbrev table for Fortran mode.")
+
+(let (abbrevs-changed)
+  ;; Use the 6th arg (SYSTEM-FLAG) of define-abbrev if possible.
+  ;; Only use `apply' to quieten the byte-compiler.
+  (mapcar
+   (function (lambda (element)
+               (condition-case nil
+                   (apply 'define-abbrev fortran-mode-abbrev-table
+                          (append element '(nil 0 t)))
+                 (wrong-number-of-arguments
+                  (apply 'define-abbrev fortran-mode-abbrev-table
+                         (append element '(nil 0)))))))
+   '((";au"   "automatic"         )
+     (";b"    "byte"              )
+     (";bd"   "block data"        )
+     (";ch"   "character"         )
+     (";cl"   "close"             )
+     (";c"    "continue"          )
+     (";cm"   "common"            )
+     (";cx"   "complex"           )
+     (";df"   "define"            )
+     (";di"   "dimension"         )
+     (";do"   "double"            )
+     (";dc"   "double complex"    )
+     (";dp"   "double precision"  )
+     (";dw"   "do while"          )
+     (";e"    "else"              )
+     (";ed"   "enddo"             )
+     (";el"   "elseif"            )
+     (";en"   "endif"             )
+     (";eq"   "equivalence"       )
+     (";ew"   "endwhere"          )
+     (";ex"   "external"          )
+     (";ey"   "entry"             )
+     (";f"    "format"            )
+     (";fa"   ".false."           )
+     (";fu"   "function"          )
+     (";g"    "goto"              )
+     (";im"   "implicit"          )
+     (";ib"   "implicit byte"     )
+     (";ic"   "implicit complex"  )
+     (";ich"  "implicit character")
+     (";ii"   "implicit integer"  )
+     (";il"   "implicit logical"  )
+     (";ir"   "implicit real"     )
+     (";inc"  "include"           )
+     (";in"   "integer"           )
+     (";intr" "intrinsic"         )
+     (";l"    "logical"           )
+     (";n"    "namelist"          )
+     (";o"    "open"              )     ; was ;op
+     (";pa"   "parameter"         )
+     (";pr"   "program"           )
+     (";ps"   "pause"             )
+     (";p"    "print"             )
+     (";rc"   "record"            )
+     (";re"   "real"              )
+     (";r"    "read"              )
+     (";rt"   "return"            )
+     (";rw"   "rewind"            )
+     (";s"    "stop"              )
+     (";sa"   "save"              )
+     (";st"   "structure"         )
+     (";sc"   "static"            )
+     (";su"   "subroutine"        )
+     (";tr"   ".true."            )
+     (";ty"   "type"              )
+     (";vo"   "volatile"          )
+     (";w"    "write"             )
+     (";wh"   "where"             ))))
 
 \f
-
 ;;;###autoload
 (defun fortran-mode ()
   "Major mode for editing Fortran code in fixed format.
@@ -585,7 +696,7 @@ Key definitions:
 
 Variables controlling indentation style and extra features:
 
-`comment-start'
+`fortran-comment-line-start'
   To use comments starting with `!', set this to the string \"!\".
 `fortran-do-indent'
   Extra indentation within DO blocks (default 3).
@@ -653,7 +764,7 @@ with no args, if that value is non-nil."
          (let (fortran-blink-matching-if ; avoid blinking delay
                indent-region-function)
            (indent-region start end nil))))
-  (set (make-local-variable 'require-final-newline) t)
+  (set (make-local-variable 'require-final-newline) mode-require-final-newline)
   ;; The syntax tables don't understand the column-0 comment-markers.
   (set (make-local-variable 'comment-use-syntax) nil)
   (set (make-local-variable 'comment-padding) "$$$")
@@ -675,7 +786,8 @@ with no args, if that value is non-nil."
        '((fortran-font-lock-keywords
           fortran-font-lock-keywords-1
           fortran-font-lock-keywords-2
-          fortran-font-lock-keywords-3)
+          fortran-font-lock-keywords-3
+          fortran-font-lock-keywords-4)
          nil t ((?/ . "$/") ("_$" . "w"))
          fortran-beginning-of-subprogram))
   (set (make-local-variable 'font-lock-syntactic-keywords)
@@ -691,9 +803,15 @@ with no args, if that value is non-nil."
   (set (make-local-variable 'add-log-current-defun-function)
        #'fortran-current-defun)
   (set (make-local-variable 'dabbrev-case-fold-search) 'case-fold-search)
-  (run-hooks 'fortran-mode-hook))
+  (set (make-local-variable 'gud-find-expr-function) 'fortran-gud-find-expr)
+  (run-mode-hooks 'fortran-mode-hook))
 
 \f
+(defun fortran-gud-find-expr ()
+  ;; Consider \n as punctuation (end of expression).
+  (with-syntax-table fortran-gud-syntax-table
+    (gud-find-c-expr)))
+
 (defsubst fortran-comment-indent ()
   "Return the indentation appropriate for the current comment line.
 This is 0 for a line matching `fortran-comment-line-start-skip', else
@@ -775,16 +893,16 @@ With non-nil ARG, uncomments the region."
 Any other key combination is executed normally."
   (interactive "*")
   (insert last-command-char)
-  (let (char event)
-    (if (fboundp 'next-command-event) ; XEmacs
-        (setq event (next-command-event)
-              char (event-to-character event))
-      (setq event (read-event)
-            char event))
+  (let* ((event (if (fboundp 'next-command-event) ; XEmacs
+                    (next-command-event)
+                  (read-event)))
+         (char (if (fboundp 'event-to-character)
+                   (event-to-character event) event)))
     ;; Insert char if not equal to `?', or if abbrev-mode is off.
-    (if (and abbrev-mode (or (eq char ??) (eq char help-char)))
+    (if (and abbrev-mode (or (eq char ??) (eq char help-char)
+                             (memq event help-event-list)))
        (fortran-abbrev-help)
-      (setq unread-command-events (list event)))))
+      (push event unread-command-events))))
 
 (defun fortran-abbrev-help ()
   "List the currently defined abbrevs in Fortran mode."
@@ -795,8 +913,7 @@ Any other key combination is executed normally."
 
 (defun fortran-prepare-abbrev-list-buffer ()
   "Create a buffer listing the Fortran mode abbreviations."
-  (save-excursion
-    (set-buffer (get-buffer-create "*Abbrevs*"))
+  (with-current-buffer (get-buffer-create "*Abbrevs*")
     (erase-buffer)
     (insert-abbrev-table-description 'fortran-mode-abbrev-table t)
     (goto-char (point-min))
@@ -853,7 +970,7 @@ See also `fortran-window-create'."
            (error (error "No room for Fortran window")))
          (message "Type SPC to continue editing.")
          (let ((char (read-event)))
-           (or (equal char (string-to-char " "))
+           (or (equal char ?\s)
                (setq unread-command-events (list char))))))
     (fortran-window-create)))
 
@@ -925,7 +1042,7 @@ Auto-indent does not happen if a numeric ARG is used."
                        fortran-minimum-statement-indent-tab
                      fortran-minimum-statement-indent-fixed) (current-column))
                  ;; In col 8 with a single tab to the left.
-                (eq ?\t (char-after (line-beginning-position))) 
+                (eq ?\t (char-after (line-beginning-position)))
                 (not (or (eq last-command 'fortran-indent-line)
                          (eq last-command
                              'fortran-indent-new-line))))
@@ -1032,6 +1149,84 @@ Directive lines are treated as comments."
     (if (not not-last-statement)
        'last-statement)))
 
+(defun fortran-looking-at-if-then ()
+  "Return non-nil if at the start of a line with an IF ... THEN statement."
+  ;; cf f90-looking-at-if-then.
+  (let ((p (point))
+        (i (fortran-beginning-if)))
+    (if i
+        (save-excursion
+          (goto-char i)
+          (beginning-of-line)
+          (= (point) p)))))
+
+;; Used in hs-special-modes-alist.
+(defun fortran-end-of-block (&optional num)
+  "Move point forward to the end of the current code block.
+With optional argument NUM, go forward that many balanced blocks.
+If NUM is negative, go backward to the start of a block.  Does
+not check for consistency of block types.  Interactively, pushes
+mark before moving point."
+  (interactive "p")
+  (if (interactive-p) (push-mark (point) t))
+  (and num (< num 0) (fortran-beginning-of-block (- num)))
+  (let ((case-fold-search t)
+        (count (or num 1)))
+    (end-of-line)
+    (while (and (> count 0)
+                (re-search-forward
+                 (concat "\\(" fortran-blocks-re
+                         (if fortran-check-all-num-for-matching-do
+                             "\\|^[ \t]*[0-9]+" "")
+                         "\\|continue\\|end\\)\\>")
+                 nil 'move))
+      (beginning-of-line)
+      (if (if (looking-at (concat "^[0-9 \t]*" fortran-if-start-re))
+              (fortran-looking-at-if-then)
+            (looking-at fortran-start-block-re))
+          (setq count (1+ count))
+        (if (or (looking-at fortran-end-block-re)
+                (and (or (looking-at "^[0-9 \t]*continue")
+                         (and fortran-check-all-num-for-matching-do
+                              (looking-at "[ \t]*[0-9]+")))
+                     (fortran-check-for-matching-do)))
+            (setq count (1- count))))
+      (end-of-line))
+    (if (> count 0) (error "Missing block end"))))
+
+(defun fortran-beginning-of-block (&optional num)
+  "Move point backwards to the start of the current code block.
+With optional argument NUM, go backward that many balanced
+blocks.  If NUM is negative, go forward to the end of a block.
+Does not check for consistency of block types.  Interactively,
+pushes mark before moving point."
+  (interactive "p")
+  (if (interactive-p) (push-mark (point) t))
+  (and num (< num 0) (fortran-end-of-block (- num)))
+  (let ((case-fold-search t)
+        (count (or num 1)))
+    (beginning-of-line)
+    (while (and (> count 0)
+                (re-search-backward
+                 (concat "\\(" fortran-blocks-re
+                         (if fortran-check-all-num-for-matching-do
+                             "\\|^[ \t]*[0-9]+" "")
+                         "\\|continue\\|end\\)\\>")
+                 nil 'move))
+      (beginning-of-line)
+      (if (if (looking-at (concat "^[0-9 \t]*" fortran-if-start-re))
+              (fortran-looking-at-if-then)
+            (looking-at fortran-start-block-re))
+          (setq count (1- count))
+        (if (or (looking-at fortran-end-block-re)
+                (and (or (looking-at "^[0-9 \t]*continue")
+                         (and fortran-check-all-num-for-matching-do
+                              (looking-at "[ \t]*[0-9]+")))
+                     (fortran-check-for-matching-do)))
+            (setq count (1+ count)))))
+    ;; Includes an un-named main program block.
+    (if (> count 0) (error "Missing block start"))))
+
 \f
 (defun fortran-blink-match (regex keyword find-begin)
   "From a line matching REGEX, blink matching KEYWORD statement line.
@@ -1058,7 +1253,7 @@ Use function FIND-BEGIN to match it."
       (if message
           (message "%s" message)
         (goto-char matching)
-        (sit-for 1)
+        (sit-for blink-matching-delay)
         (goto-char end-point)))))
 
 (defun fortran-blink-matching-if ()
@@ -1455,7 +1650,7 @@ notes: 1) A non-zero/non-blank character in column 5 indicates a continuation
            (let* ((char (if (stringp fortran-comment-indent-char)
                             (aref fortran-comment-indent-char 0)
                           fortran-comment-indent-char))
-                  (chars (string ?  ?\t char)))
+                  (chars (string ?\s ?\t char)))
              (goto-char (match-end 0))
              (skip-chars-backward chars)
              (delete-region (point) (progn (skip-chars-forward chars)
@@ -1465,7 +1660,7 @@ notes: 1) A non-zero/non-blank character in column 5 indicates a continuation
          (if indent-tabs-mode
              (goto-char (match-end 0))
            (delete-char 2)
-           (insert-char ?  5)
+           (insert-char ?\s 5)
            (insert fortran-continuation-string))
        (if (looking-at " \\{5\\}[^ 0\n]")
            (if indent-tabs-mode
@@ -1634,56 +1829,68 @@ If ALL is nil, only match comments that start in column > 0."
         (bol (line-beginning-position))
         (eol (line-end-position))
         (bos (min eol (+ bol (fortran-current-line-indentation))))
+         ;; If in a string at fill-column, break it either before the
+         ;; initial quote, or at fill-col (if string is too long).
         (quote
          (save-excursion
            (goto-char bol)
            ;; OK to break quotes on comment lines.
            (unless (looking-at fortran-comment-line-start-skip)
               (let (fcpoint start)
-             (move-to-column fill-column)
-             (when (fortran-is-in-string-p (setq fcpoint (point)))
-                (save-excursion
-                  (re-search-backward "\\S\"\\s\"\\S\"" bol t)
-                  (setq start
-                        (if fortran-break-before-delimiters
-                            (point)
-                          (1+ (point)))))
-                (if (re-search-forward "\\S\"\\s\"\\S\"" eol t)
-                    (backward-char 2))
-                ;; If the current string is longer than 72 - 6 chars,
-                ;; break it at the fill column (else infinite loop).
-                (if (> (- (point) start)
-                       (- fill-column 6 fortran-continuation-indent))
-                    fcpoint
-                  start))))))
+                (move-to-column fill-column)
+                (when (fortran-is-in-string-p (setq fcpoint (point)))
+                  (save-excursion
+                    (re-search-backward "\\S\"\\s\"\\S\"?" bol t)
+                    (setq start
+                          (if fortran-break-before-delimiters
+                              (point)
+                            (1+ (point)))))
+                  (if (re-search-forward "\\S\"\\s\"\\S\"" eol t)
+                      (backward-char 2))
+                  ;; If the current string is longer than (fill-column
+                  ;; - 6) chars, break it at the fill column (else
+                  ;; infinite loop).
+                  (if (> (- (point) start)
+                         (- fill-column 6 fortran-continuation-indent))
+                      fcpoint
+                    start))))))
         ;; Decide where to split the line. If a position for a quoted
         ;; string was found above then use that, else break the line
-        ;; before the last delimiter.
-        ;; Delimiters are whitespace, commas, and operators.
-        ;; Will break before a pair of *'s.
+        ;; before/after the last delimiter.
         (fill-point
          (or quote
              (save-excursion
-               (move-to-column (1+ fill-column))
-                ;; GM Make this a defcustom as in f90-mode? Add ", (?
-               (skip-chars-backward "^ \t\n,'+-/*=)"
-;;;             (if fortran-break-before-delimiters
-;;;                 "^ \t\n,'+-/*=" "^ \t\n,'+-/*=)")
-                )
-               (when (<= (point) (1+ bos))
+                ;; If f-b-b-d is t, have an extra column to play with,
+                ;; since delimiter gets shifted to new line.
+                (move-to-column (if fortran-break-before-delimiters
+                                    (1+ fill-column)
+                                  fill-column))
+                (let ((repeat t))
+                  (while repeat
+                    (setq repeat nil)
+                    ;; Adapted from f90-find-breakpoint.
+                    (re-search-backward fortran-break-delimiters-re bol)
+                    (if (not fortran-break-before-delimiters)
+                        (if (looking-at fortran-no-break-re)
+                            ;; Deal with cases such as "**" split over
+                            ;; fill-col. Simpler alternative would be
+                            ;; to start from (1- fill-column) above.
+                            (if (> (+ 2 (current-column)) fill-column)
+                                (setq repeat t)
+                              (forward-char 2))
+                          (forward-char 1))
+                      (backward-char)
+                      (or (looking-at fortran-no-break-re)
+                          (forward-char)))))
+                ;; Line indented beyond fill-column?
+               (when (<= (point) bos)
                   (move-to-column (1+ fill-column))
                   ;; What is this doing???
                   (or (re-search-forward "[\t\n,'+-/*)=]" eol t)
                       (goto-char bol)))
                (if (bolp)
-                   (re-search-forward "[ \t]" opoint t)
-                 (backward-char)
-                 (if (looking-at "\\s\"")
-                     (forward-char)
-                   (skip-chars-backward " \t\*")))
-               (if fortran-break-before-delimiters
-                   (point)
-                 (1+ (point)))))))
+                   (re-search-forward "[ \t]" opoint t))
+                (point)))))
     ;; If we are in an in-line comment, don't break unless the
     ;; line of code is longer than it should be. Otherwise
     ;; break the line at the column computed above.
@@ -1711,8 +1918,7 @@ If ALL is nil, only match comments that start in column > 0."
 
 (defun fortran-break-line ()
   "Call `fortran-split-line'.  Joins continuation lines first, then refills."
-  (let ((opoint (point))
-       (bol (line-beginning-position))
+  (let ((bol (line-beginning-position))
        (comment-string
         (save-excursion
           (if (fortran-find-comment-start-skip)
@@ -1830,4 +2036,5 @@ Supplying prefix arg DO-SPACE prevents stripping the whitespace."
 
 (provide 'fortran)
 
+;; arch-tag: 74935096-21c4-4cab-8ee5-6ef16090dc04
 ;;; fortran.el ends here