cl-ppcre-2.0.3/0000755000175700010010000000000011271772245011447 5ustar ediNonecl-ppcre-2.0.3/api.lisp0000644000175700010010000017177711254505512013125 0ustar ediNone;;; -*- Mode: LISP; Syntax: COMMON-LISP; Package: CL-PPCRE; Base: 10 -*- ;;; $Header: /usr/local/cvsrep/cl-ppcre/api.lisp,v 1.85 2009/09/17 19:17:30 edi Exp $ ;;; The external API for creating and using scanners. ;;; Copyright (c) 2002-2009, Dr. Edmund Weitz. All rights reserved. ;;; Redistribution and use in source and binary forms, with or without ;;; modification, are permitted provided that the following conditions ;;; are met: ;;; * Redistributions of source code must retain the above copyright ;;; notice, this list of conditions and the following disclaimer. ;;; * Redistributions in binary form must reproduce the above ;;; copyright notice, this list of conditions and the following ;;; disclaimer in the documentation and/or other materials ;;; provided with the distribution. ;;; THIS SOFTWARE IS PROVIDED BY THE AUTHOR 'AS IS' AND ANY EXPRESSED ;;; OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED ;;; WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ;;; ARE DISCLAIMED. IN NO EVENT SHALL THE AUTHOR BE LIABLE FOR ANY ;;; DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL ;;; DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE ;;; GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS ;;; INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, ;;; WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING ;;; NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE OF THIS ;;; SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. (in-package :cl-ppcre) (defgeneric create-scanner (regex &key case-insensitive-mode multi-line-mode single-line-mode extended-mode destructive) (:documentation "Accepts a regular expression - either as a parse-tree or as a string - and returns a scan closure which will scan strings for this regular expression and a list mapping registers to their names \(NIL stands for unnamed ones). The \"mode\" keyboard arguments are equivalent to the imsx modifiers in Perl. If DESTRUCTIVE is not NIL, the function is allowed to destructively modify its first argument \(but only if it's a parse tree).")) #-:use-acl-regexp2-engine (defmethod create-scanner ((regex-string string) &key case-insensitive-mode multi-line-mode single-line-mode extended-mode destructive) (declare #.*standard-optimize-settings*) (declare (ignore destructive)) ;; parse the string into a parse-tree and then call CREATE-SCANNER ;; again (let* ((*extended-mode-p* extended-mode) (quoted-regex-string (if *allow-quoting* (quote-sections (clean-comments regex-string extended-mode)) regex-string)) (*syntax-error-string* (copy-seq quoted-regex-string))) ;; wrap the result with :GROUP to avoid infinite loops for ;; constant strings (create-scanner (cons :group (list (parse-string quoted-regex-string))) :case-insensitive-mode case-insensitive-mode :multi-line-mode multi-line-mode :single-line-mode single-line-mode :destructive t))) #-:use-acl-regexp2-engine (defmethod create-scanner ((scanner function) &key case-insensitive-mode multi-line-mode single-line-mode extended-mode destructive) (declare #.*standard-optimize-settings*) (declare (ignore destructive)) (when (or case-insensitive-mode multi-line-mode single-line-mode extended-mode) (signal-invocation-error "You can't use the keyword arguments to modify an existing scanner.")) scanner) #-:use-acl-regexp2-engine (defmethod create-scanner ((parse-tree t) &key case-insensitive-mode multi-line-mode single-line-mode extended-mode destructive) (declare #.*standard-optimize-settings*) (when extended-mode (signal-invocation-error "Extended mode doesn't make sense in parse trees.")) ;; convert parse-tree into internal representation REGEX and at the ;; same time compute the number of registers and the constant string ;; (or anchor) the regex starts with (if any) (unless destructive (setq parse-tree (copy-tree parse-tree))) (let (flags) (if single-line-mode (push :single-line-mode-p flags)) (if multi-line-mode (push :multi-line-mode-p flags)) (if case-insensitive-mode (push :case-insensitive-p flags)) (when flags (setq parse-tree (list :group (cons :flags flags) parse-tree)))) (let ((*syntax-error-string* nil)) (multiple-value-bind (regex reg-num starts-with reg-names) (convert parse-tree) ;; simplify REGEX by flattening nested SEQ and ALTERNATION ;; constructs and gathering STR objects (let ((regex (gather-strings (flatten regex)))) ;; set the MIN-REST slots of the REPETITION objects (compute-min-rest regex 0) ;; set the OFFSET slots of the STR objects (compute-offsets regex 0) (let* (end-string-offset end-anchored-p ;; compute the constant string the regex ends with (if ;; any) and at the same time set the special variables ;; END-STRING-OFFSET and END-ANCHORED-P (end-string (end-string regex)) ;; if we found a non-zero-length end-string we create an ;; efficient search function for it (end-string-test (and end-string (plusp (len end-string)) (if (= 1 (len end-string)) (create-char-searcher (schar (str end-string) 0) (case-insensitive-p end-string)) (create-bmh-matcher (str end-string) (case-insensitive-p end-string))))) ;; initialize the counters for CREATE-MATCHER-AUX (*rep-num* 0) (*zero-length-num* 0) ;; create the actual matcher function (which does all the ;; work of matching the regular expression) corresponding ;; to REGEX and at the same time set the special ;; variables *REP-NUM* and *ZERO-LENGTH-NUM* (match-fn (create-matcher-aux regex #'identity)) ;; if the regex starts with a string we create an ;; efficient search function for it (start-string-test (and (typep starts-with 'str) (plusp (len starts-with)) (if (= 1 (len starts-with)) (create-char-searcher (schar (str starts-with) 0) (case-insensitive-p starts-with)) (create-bmh-matcher (str starts-with) (case-insensitive-p starts-with)))))) (declare (special end-string-offset end-anchored-p end-string)) ;; now create the scanner and return it (values (create-scanner-aux match-fn (regex-min-length regex) (or (start-anchored-p regex) ;; a dot in single-line-mode also ;; implicitly anchors the regex at ;; the start, i.e. if we can't match ;; from the first position we won't ;; match at all (and (typep starts-with 'everything) (single-line-p starts-with))) starts-with start-string-test ;; only mark regex as end-anchored if we ;; found a non-zero-length string before ;; the anchor (and end-string-test end-anchored-p) end-string-test (if end-string-test (len end-string) nil) end-string-offset *rep-num* *zero-length-num* reg-num) reg-names)))))) #+:use-acl-regexp2-engine (declaim (inline create-scanner)) #+:use-acl-regexp2-engine (defmethod create-scanner ((scanner regexp::regular-expression) &key case-insensitive-mode multi-line-mode single-line-mode extended-mode destructive) (declare #.*standard-optimize-settings*) (declare (ignore destructive)) (when (or case-insensitive-mode multi-line-mode single-line-mode extended-mode) (signal-invocation-error "You can't use the keyword arguments to modify an existing scanner.")) scanner) #+:use-acl-regexp2-engine (defmethod create-scanner ((parse-tree t) &key case-insensitive-mode multi-line-mode single-line-mode extended-mode destructive) (declare #.*standard-optimize-settings*) (declare (ignore destructive)) (excl:compile-re parse-tree :case-fold case-insensitive-mode :ignore-whitespace extended-mode :multiple-lines multi-line-mode :single-line single-line-mode :return :index)) (defgeneric scan (regex target-string &key start end real-start-pos) (:documentation "Searches TARGET-STRING from START to END and tries to match REGEX. On success returns four values - the start of the match, the end of the match, and two arrays denoting the beginnings and ends of register matches. On failure returns NIL. REGEX can be a string which will be parsed according to Perl syntax, a parse tree, or a pre-compiled scanner created by CREATE-SCANNER. TARGET-STRING will be coerced to a simple string if it isn't one already. The REAL-START-POS parameter should be ignored - it exists only for internal purposes.")) #-:use-acl-regexp2-engine (defmethod scan ((regex-string string) target-string &key (start 0) (end (length target-string)) ((:real-start-pos *real-start-pos*) nil)) (declare #.*standard-optimize-settings*) ;; note that the scanners are optimized for simple strings so we ;; have to coerce TARGET-STRING into one if it isn't already (funcall (create-scanner regex-string) (maybe-coerce-to-simple-string target-string) start end)) #-:use-acl-regexp2-engine (defmethod scan ((scanner function) target-string &key (start 0) (end (length target-string)) ((:real-start-pos *real-start-pos*) nil)) (declare #.*standard-optimize-settings*) (funcall scanner (maybe-coerce-to-simple-string target-string) start end)) #-:use-acl-regexp2-engine (defmethod scan ((parse-tree t) target-string &key (start 0) (end (length target-string)) ((:real-start-pos *real-start-pos*) nil)) (declare #.*standard-optimize-settings*) (funcall (create-scanner parse-tree) (maybe-coerce-to-simple-string target-string) start end)) #+:use-acl-regexp2-engine (declaim (inline scan)) #+:use-acl-regexp2-engine (defmethod scan ((parse-tree t) target-string &key (start 0) (end (length target-string)) ((:real-start-pos *real-start-pos*) nil)) (declare #.*standard-optimize-settings*) (when (< end start) (return-from scan nil)) (let ((results (multiple-value-list (excl:match-re parse-tree target-string :start start :end end :return :index)))) (declare (dynamic-extent results)) (cond ((null (first results)) nil) (t (let* ((no-of-regs (- (length results) 2)) (reg-starts (make-array no-of-regs :element-type '(or null fixnum))) (reg-ends (make-array no-of-regs :element-type '(or null fixnum))) (match (second results))) (loop for (start . end) in (cddr results) for i from 0 do (setf (aref reg-starts i) start (aref reg-ends i) end)) (values (car match) (cdr match) reg-starts reg-ends)))))) #-:cormanlisp (define-compiler-macro scan (&whole form &environment env regex target-string &rest rest) "Make sure that constant forms are compiled into scanners at compile time." (cond ((constantp regex env) `(scan (load-time-value (create-scanner ,regex)) ,target-string ,@rest)) (t form))) (defun scan-to-strings (regex target-string &key (start 0) (end (length target-string)) sharedp) "Like SCAN but returns substrings of TARGET-STRING instead of positions, i.e. this function returns two values on success: the whole match as a string plus an array of substrings (or NILs) corresponding to the matched registers. If SHAREDP is true, the substrings may share structure with TARGET-STRING." (declare #.*standard-optimize-settings*) (multiple-value-bind (match-start match-end reg-starts reg-ends) (scan regex target-string :start start :end end) (unless match-start (return-from scan-to-strings nil)) (let ((substr-fn (if sharedp #'nsubseq #'subseq))) (values (funcall substr-fn target-string match-start match-end) (map 'vector (lambda (reg-start reg-end) (if reg-start (funcall substr-fn target-string reg-start reg-end) nil)) reg-starts reg-ends))))) #-:cormanlisp (define-compiler-macro scan-to-strings (&whole form &environment env regex target-string &rest rest) "Make sure that constant forms are compiled into scanners at compile time." (cond ((constantp regex env) `(scan-to-strings (load-time-value (create-scanner ,regex)) ,target-string ,@rest)) (t form))) (defmacro register-groups-bind (var-list (regex target-string &key start end sharedp) &body body) "Executes BODY with the variables in VAR-LIST bound to the corresponding register groups after TARGET-STRING has been matched against REGEX, i.e. each variable is either bound to a string or to NIL. If there is no match, BODY is _not_ executed. For each element of VAR-LIST which is NIL there's no binding to the corresponding register group. The number of variables in VAR-LIST must not be greater than the number of register groups. If SHAREDP is true, the substrings may share structure with TARGET-STRING." (with-rebinding (target-string) (with-unique-names (match-start match-end reg-starts reg-ends start-index substr-fn) `(multiple-value-bind (,match-start ,match-end ,reg-starts ,reg-ends) (scan ,regex ,target-string :start (or ,start 0) :end (or ,end (length ,target-string))) (declare (ignore ,match-end)) (when ,match-start (let* ,(cons `(,substr-fn (if ,sharedp #'nsubseq #'subseq)) (loop for (function var) in (normalize-var-list var-list) for counter from 0 when var collect `(,var (let ((,start-index (aref ,reg-starts ,counter))) (if ,start-index (funcall ,function (funcall ,substr-fn ,target-string ,start-index (aref ,reg-ends ,counter))) nil))))) ,@body)))))) (defmacro do-scans ((match-start match-end reg-starts reg-ends regex target-string &optional result-form &key start end) &body body &environment env) "Iterates over TARGET-STRING and tries to match REGEX as often as possible evaluating BODY with MATCH-START, MATCH-END, REG-STARTS, and REG-ENDS bound to the four return values of each match in turn. After the last match, returns RESULT-FORM if provided or NIL otherwise. An implicit block named NIL surrounds DO-SCANS; RETURN may be used to terminate the loop immediately. If REGEX matches an empty string the scan is continued one position behind this match. BODY may start with declarations." (with-rebinding (target-string) (with-unique-names (%start %end %regex scanner) (declare (ignorable %regex scanner)) ;; the NIL BLOCK to enable exits via (RETURN ...) `(block nil (let* ((,%start (or ,start 0)) (,%end (or ,end (length ,target-string))) ,@(unless (constantp regex env) ;; leave constant regular expressions as they are - ;; SCAN's compiler macro will take care of them; ;; otherwise create a scanner unless the regex is ;; already a function (otherwise SCAN will do this ;; on each iteration) `((,%regex ,regex) (,scanner (typecase ,%regex (function ,%regex) (t (create-scanner ,%regex))))))) ;; coerce TARGET-STRING to a simple string unless it is one ;; already (otherwise SCAN will do this on each iteration) (setq ,target-string (maybe-coerce-to-simple-string ,target-string)) (loop ;; invoke SCAN and bind the returned values to the ;; provided variables (multiple-value-bind (,match-start ,match-end ,reg-starts ,reg-ends) (scan ,(cond ((constantp regex env) regex) (t scanner)) ,target-string :start ,%start :end ,%end :real-start-pos (or ,start 0)) ;; declare the variables to be IGNORABLE to prevent the ;; compiler from issuing warnings (declare (ignorable ,match-start ,match-end ,reg-starts ,reg-ends)) (unless ,match-start ;; stop iteration on first failure (return ,result-form)) ;; execute BODY (wrapped in LOCALLY so it can start with ;; declarations) (locally ,@body) ;; advance by one position if we had a zero-length match (setq ,%start (if (= ,match-start ,match-end) (1+ ,match-end) ,match-end))))))))) (defmacro do-matches ((match-start match-end regex target-string &optional result-form &key start end) &body body) "Iterates over TARGET-STRING and tries to match REGEX as often as possible evaluating BODY with MATCH-START and MATCH-END bound to the start/end positions of each match in turn. After the last match, returns RESULT-FORM if provided or NIL otherwise. An implicit block named NIL surrounds DO-MATCHES; RETURN may be used to terminate the loop immediately. If REGEX matches an empty string the scan is continued one position behind this match. BODY may start with declarations." ;; this is a simplified form of DO-SCANS - we just provide two dummy ;; vars and ignore them (with-unique-names (reg-starts reg-ends) `(do-scans (,match-start ,match-end ,reg-starts ,reg-ends ,regex ,target-string ,result-form :start ,start :end ,end) ,@body))) (defmacro do-matches-as-strings ((match-var regex target-string &optional result-form &key start end sharedp) &body body) "Iterates over TARGET-STRING and tries to match REGEX as often as possible evaluating BODY with MATCH-VAR bound to the substring of TARGET-STRING corresponding to each match in turn. After the last match, returns RESULT-FORM if provided or NIL otherwise. An implicit block named NIL surrounds DO-MATCHES-AS-STRINGS; RETURN may be used to terminate the loop immediately. If REGEX matches an empty string the scan is continued one position behind this match. If SHAREDP is true, the substrings may share structure with TARGET-STRING. BODY may start with declarations." (with-rebinding (target-string) (with-unique-names (match-start match-end substr-fn) `(let ((,substr-fn (if ,sharedp #'nsubseq #'subseq))) ;; simple use DO-MATCHES to extract the substrings (do-matches (,match-start ,match-end ,regex ,target-string ,result-form :start ,start :end ,end) (let ((,match-var (funcall ,substr-fn ,target-string ,match-start ,match-end))) ,@body)))))) (defmacro do-register-groups (var-list (regex target-string &optional result-form &key start end sharedp) &body body) "Iterates over TARGET-STRING and tries to match REGEX as often as possible evaluating BODY with the variables in VAR-LIST bound to the corresponding register groups for each match in turn, i.e. each variable is either bound to a string or to NIL. For each element of VAR-LIST which is NIL there's no binding to the corresponding register group. The number of variables in VAR-LIST must not be greater than the number of register groups. After the last match, returns RESULT-FORM if provided or NIL otherwise. An implicit block named NIL surrounds DO-REGISTER-GROUPS; RETURN may be used to terminate the loop immediately. If REGEX matches an empty string the scan is continued one position behind this match. If SHAREDP is true, the substrings may share structure with TARGET-STRING. BODY may start with declarations." (with-rebinding (target-string) (with-unique-names (substr-fn match-start match-end reg-starts reg-ends start-index) `(let ((,substr-fn (if ,sharedp #'nsubseq #'subseq))) (do-scans (,match-start ,match-end ,reg-starts ,reg-ends ,regex ,target-string ,result-form :start ,start :end ,end) (let ,(loop for (function var) in (normalize-var-list var-list) for counter from 0 when var collect `(,var (let ((,start-index (aref ,reg-starts ,counter))) (if ,start-index (funcall ,function (funcall ,substr-fn ,target-string ,start-index (aref ,reg-ends ,counter))) nil)))) ,@body)))))) (defun all-matches (regex target-string &key (start 0) (end (length target-string))) "Returns a list containing the start and end positions of all matches of REGEX against TARGET-STRING, i.e. if there are N matches the list contains (* 2 N) elements. If REGEX matches an empty string the scan is continued one position behind this match." (declare #.*standard-optimize-settings*) (let (result-list) (do-matches (match-start match-end regex target-string (nreverse result-list) :start start :end end) (push match-start result-list) (push match-end result-list)))) #-:cormanlisp (define-compiler-macro all-matches (&whole form &environment env regex &rest rest) "Make sure that constant forms are compiled into scanners at compile time." (cond ((constantp regex env) `(all-matches (load-time-value (create-scanner ,regex)) ,@rest)) (t form))) (defun all-matches-as-strings (regex target-string &key (start 0) (end (length target-string)) sharedp) "Returns a list containing all substrings of TARGET-STRING which match REGEX. If REGEX matches an empty string the scan is continued one position behind this match. If SHAREDP is true, the substrings may share structure with TARGET-STRING." (declare #.*standard-optimize-settings*) (let (result-list) (do-matches-as-strings (match regex target-string (nreverse result-list) :start start :end end :sharedp sharedp) (push match result-list)))) #-:cormanlisp (define-compiler-macro all-matches-as-strings (&whole form &environment env regex &rest rest) "Make sure that constant forms are compiled into scanners at compile time." (cond ((constantp regex env) `(all-matches-as-strings (load-time-value (create-scanner ,regex)) ,@rest)) (t form))) (defun split (regex target-string &key (start 0) (end (length target-string)) limit with-registers-p omit-unmatched-p sharedp) "Matches REGEX against TARGET-STRING as often as possible and returns a list of the substrings between the matches. If WITH-REGISTERS-P is true, substrings corresponding to matched registers are inserted into the list as well. If OMIT-UNMATCHED-P is true, unmatched registers will simply be left out, otherwise they will show up as NIL. LIMIT limits the number of elements returned - registers aren't counted. If LIMIT is NIL \(or 0 which is equivalent), trailing empty strings are removed from the result list. If REGEX matches an empty string the scan is continued one position behind this match. If SHAREDP is true, the substrings may share structure with TARGET-STRING." (declare #.*standard-optimize-settings*) ;; initialize list of positions POS-LIST to extract substrings with ;; START so that the start of the next match will mark the end of ;; the first substring (let ((pos-list (list start)) (counter 0)) ;; how would Larry Wall do it? (when (eql limit 0) (setq limit nil)) (do-scans (match-start match-end reg-starts reg-ends regex target-string nil :start start :end end) (unless (and (= match-start match-end) (= match-start (car pos-list))) ;; push start of match on list unless this would be an empty ;; string adjacent to the last element pushed onto the list (when (and limit (>= (incf counter) limit)) (return)) (push match-start pos-list) (when with-registers-p ;; optionally insert matched registers (loop for reg-start across reg-starts for reg-end across reg-ends if reg-start ;; but only if they've matched do (push reg-start pos-list) (push reg-end pos-list) else unless omit-unmatched-p ;; or if we're allowed to insert NIL instead do (push nil pos-list) (push nil pos-list))) ;; now end of match (push match-end pos-list))) ;; end of whole string (push end pos-list) ;; now collect substrings (nreverse (loop with substr-fn = (if sharedp #'nsubseq #'subseq) with string-seen = nil for (this-end this-start) on pos-list by #'cddr ;; skip empty strings from end of list if (or limit (setq string-seen (or string-seen (and this-start (> this-end this-start))))) collect (if this-start (funcall substr-fn target-string this-start this-end) nil))))) #-:cormanlisp (define-compiler-macro split (&whole form &environment env regex target-string &rest rest) "Make sure that constant forms are compiled into scanners at compile time." (cond ((constantp regex env) `(split (load-time-value (create-scanner ,regex)) ,target-string ,@rest)) (t form))) (defun string-case-modifier (str from to start end) (declare #.*standard-optimize-settings*) (declare (fixnum from to start end)) "Checks whether all words in STR between FROM and TO are upcased, downcased or capitalized and returns a function which applies a corresponding case modification to strings. Returns #'IDENTITY otherwise, especially if words in the target area extend beyond FROM or TO. STR is supposed to be bounded by START and END. It is assumed that \(<= START FROM TO END)." (case (if (or (<= to from) (and (< start from) (alphanumericp (char str (1- from))) (alphanumericp (char str from))) (and (< to end) (alphanumericp (char str to)) (alphanumericp (char str (1- to))))) ;; if it's a zero-length string or if words extend beyond FROM ;; or TO we return NIL, i.e. #'IDENTITY nil ;; otherwise we loop through STR from FROM to TO (loop with last-char-both-case with current-result for index of-type fixnum from from below to for chr = (char str index) do (cond ((not #-:cormanlisp (both-case-p chr) #+:cormanlisp (or (upper-case-p chr) (lower-case-p chr))) ;; this character doesn't have a case so we ;; consider it as a word boundary (note that ;; this differs from how \b works in Perl) (setq last-char-both-case nil)) ((upper-case-p chr) ;; an uppercase character (setq current-result (if last-char-both-case ;; not the first character in a (case current-result ((:undecided) :upcase) ((:downcase :capitalize) (return nil)) ((:upcase) current-result)) (case current-result ((nil) :undecided) ((:downcase) (return nil)) ((:capitalize :upcase) current-result))) last-char-both-case t)) (t ;; a lowercase character (setq current-result (case current-result ((nil) :downcase) ((:undecided) :capitalize) ((:downcase) current-result) ((:capitalize) (if last-char-both-case current-result (return nil))) ((:upcase) (return nil))) last-char-both-case t))) finally (return current-result))) ((nil) #'identity) ((:undecided :upcase) #'string-upcase) ((:downcase) #'string-downcase) ((:capitalize) #'string-capitalize))) ;; first create a scanner to identify the special parts of the ;; replacement string (eat your own dog food...) (defgeneric build-replacement-template (replacement-string) (declare #.*standard-optimize-settings*) (:documentation "Converts a replacement string for REGEX-REPLACE or REGEX-REPLACE-ALL into a replacement template which is an S-expression.")) #-:cormanlisp (let* ((*use-bmh-matchers* nil) (reg-scanner (create-scanner "\\\\(?:\\\\|\\{\\d+\\}|\\d+|&|`|')"))) (defmethod build-replacement-template ((replacement-string string)) (declare #.*standard-optimize-settings*) (let ((from 0) ;; COLLECTOR will hold the (reversed) template (collector '())) ;; scan through all special parts of the replacement string (do-matches (match-start match-end reg-scanner replacement-string) (when (< from match-start) ;; strings between matches are copied verbatim (push (subseq replacement-string from match-start) collector)) ;; PARSE-START is true if the pattern matched a number which ;; refers to a register (let* ((parse-start (position-if #'digit-char-p replacement-string :start match-start :end match-end)) (token (if parse-start (1- (parse-integer replacement-string :start parse-start :junk-allowed t)) ;; if we didn't match a number we convert the ;; character to a symbol (case (char replacement-string (1+ match-start)) ((#\&) :match) ((#\`) :before-match) ((#\') :after-match) ((#\\) :backslash))))) (when (and (numberp token) (< token 0)) ;; make sure we don't accept something like "\\0" (signal-invocation-error "Illegal substring ~S in replacement string." (subseq replacement-string match-start match-end))) (push token collector)) ;; remember where the match ended (setq from match-end)) (when (< from (length replacement-string)) ;; push the rest of the replacement string onto the list (push (subseq replacement-string from) collector)) (nreverse collector)))) #-:cormanlisp (defmethod build-replacement-template ((replacement-function function)) (declare #.*standard-optimize-settings*) (list replacement-function)) #-:cormanlisp (defmethod build-replacement-template ((replacement-function-symbol symbol)) (declare #.*standard-optimize-settings*) (list replacement-function-symbol)) #-:cormanlisp (defmethod build-replacement-template ((replacement-list list)) (declare #.*standard-optimize-settings*) replacement-list) ;;; Corman Lisp's methods can't be closures... :( #+:cormanlisp (let* ((*use-bmh-matchers* nil) (reg-scanner (create-scanner "\\\\(?:\\\\|\\{\\d+\\}|\\d+|&|`|')"))) (defun build-replacement-template (replacement) (declare #.*standard-optimize-settings*) (typecase replacement (string (let ((from 0) ;; COLLECTOR will hold the (reversed) template (collector '())) ;; scan through all special parts of the replacement string (do-matches (match-start match-end reg-scanner replacement) (when (< from match-start) ;; strings between matches are copied verbatim (push (subseq replacement from match-start) collector)) ;; PARSE-START is true if the pattern matched a number which ;; refers to a register (let* ((parse-start (position-if #'digit-char-p replacement :start match-start :end match-end)) (token (if parse-start (1- (parse-integer replacement :start parse-start :junk-allowed t)) ;; if we didn't match a number we convert the ;; character to a symbol (case (char replacement (1+ match-start)) ((#\&) :match) ((#\`) :before-match) ((#\') :after-match) ((#\\) :backslash))))) (when (and (numberp token) (< token 0)) ;; make sure we don't accept something like "\\0" (signal-invocation-error "Illegal substring ~S in replacement string." (subseq replacement match-start match-end))) (push token collector)) ;; remember where the match ended (setq from match-end)) (when (< from (length replacement)) ;; push the rest of the replacement string onto the list (push (nsubseq replacement from) collector)) (nreverse collector))) (list replacement) (t (list replacement))))) (defun build-replacement (replacement-template target-string start end match-start match-end reg-starts reg-ends simple-calls element-type) (declare #.*standard-optimize-settings*) "Accepts a replacement template and the current values from the matching process in REGEX-REPLACE or REGEX-REPLACE-ALL and returns the corresponding string." ;; the upper exclusive bound of the register numbers in the regular ;; expression (let ((reg-bound (if reg-starts (array-dimension reg-starts 0) 0))) (with-output-to-string (s nil :element-type element-type) (loop for token in replacement-template do (typecase token (string ;; transfer string parts verbatim (write-string token s)) (integer ;; replace numbers with the corresponding registers (when (>= token reg-bound) ;; but only if the register was referenced in the ;; regular expression (signal-invocation-error "Reference to non-existent register ~A in replacement string." (1+ token))) (when (svref reg-starts token) ;; and only if it matched, i.e. no match results ;; in an empty string (write-string target-string s :start (svref reg-starts token) :end (svref reg-ends token)))) (function (write-string (cond (simple-calls (apply token (nsubseq target-string match-start match-end) (map 'list (lambda (reg-start reg-end) (and reg-start (nsubseq target-string reg-start reg-end))) reg-starts reg-ends))) (t (funcall token target-string start end match-start match-end reg-starts reg-ends))) s)) (symbol (case token ((:backslash) ;; just a backslash (write-char #\\ s)) ((:match) ;; the whole match (write-string target-string s :start match-start :end match-end)) ((:before-match) ;; the part of the target string before the match (write-string target-string s :start start :end match-start)) ((:after-match) ;; the part of the target string after the match (write-string target-string s :start match-end :end end)) (otherwise (write-string (cond (simple-calls (apply token (nsubseq target-string match-start match-end) (map 'list (lambda (reg-start reg-end) (and reg-start (nsubseq target-string reg-start reg-end))) reg-starts reg-ends))) (t (funcall token target-string start end match-start match-end reg-starts reg-ends))) s))))))))) (defun replace-aux (target-string replacement pos-list reg-list start end preserve-case simple-calls element-type) "Auxiliary function used by REGEX-REPLACE and REGEX-REPLACE-ALL. POS-LIST contains a list with the start and end positions of all matches while REG-LIST contains a list of arrays representing the corresponding register start and end positions." (declare #.*standard-optimize-settings*) ;; build the template once before we start the loop (let ((replacement-template (build-replacement-template replacement))) (with-output-to-string (s nil :element-type element-type) ;; loop through all matches and take the start and end of the ;; whole string into account (loop for (from to) on (append (list start) pos-list (list end)) ;; alternate between replacement and no replacement for replace = nil then (and (not replace) to) for reg-starts = (if replace (pop reg-list) nil) for reg-ends = (if replace (pop reg-list) nil) for curr-replacement = (if replace ;; build the replacement string (build-replacement replacement-template target-string start end from to reg-starts reg-ends simple-calls element-type) nil) while to if replace do (write-string (if preserve-case ;; modify the case of the replacement ;; string if necessary (funcall (string-case-modifier target-string from to start end) curr-replacement) curr-replacement) s) else ;; no replacement do (write-string target-string s :start from :end to))))) (defun regex-replace (regex target-string replacement &key (start 0) (end (length target-string)) preserve-case simple-calls (element-type #+:lispworks 'lw:simple-char #-:lispworks 'character)) "Try to match TARGET-STRING between START and END against REGEX and replace the first match with REPLACEMENT. Two values are returned; the modified string, and T if REGEX matched or NIL otherwise. REPLACEMENT can be a string which may contain the special substrings \"\\&\" for the whole match, \"\\`\" for the part of TARGET-STRING before the match, \"\\'\" for the part of TARGET-STRING after the match, \"\\N\" or \"\\{N}\" for the Nth register where N is a positive integer. REPLACEMENT can also be a function designator in which case the match will be replaced with the result of calling the function designated by REPLACEMENT with the arguments TARGET-STRING, START, END, MATCH-START, MATCH-END, REG-STARTS, and REG-ENDS. (REG-STARTS and REG-ENDS are arrays holding the start and end positions of matched registers or NIL - the meaning of the other arguments should be obvious.) Finally, REPLACEMENT can be a list where each element is a string, one of the symbols :MATCH, :BEFORE-MATCH, or :AFTER-MATCH - corresponding to \"\\&\", \"\\`\", and \"\\'\" above -, an integer N - representing register (1+ N) -, or a function designator. If PRESERVE-CASE is true, the replacement will try to preserve the case (all upper case, all lower case, or capitalized) of the match. The result will always be a fresh string, even if REGEX doesn't match. ELEMENT-TYPE is the element type of the resulting string." (declare #.*standard-optimize-settings*) (multiple-value-bind (match-start match-end reg-starts reg-ends) (scan regex target-string :start start :end end) (if match-start (values (replace-aux target-string replacement (list match-start match-end) (list reg-starts reg-ends) start end preserve-case simple-calls element-type) t) (values (subseq target-string start end) nil)))) #-:cormanlisp (define-compiler-macro regex-replace (&whole form &environment env regex target-string replacement &rest rest) "Make sure that constant forms are compiled into scanners at compile time." (cond ((constantp regex env) `(regex-replace (load-time-value (create-scanner ,regex)) ,target-string ,replacement ,@rest)) (t form))) (defun regex-replace-all (regex target-string replacement &key (start 0) (end (length target-string)) preserve-case simple-calls (element-type #+:lispworks 'lw:simple-char #-:lispworks 'character)) "Try to match TARGET-STRING between START and END against REGEX and replace all matches with REPLACEMENT. Two values are returned; the modified string, and T if REGEX matched or NIL otherwise. REPLACEMENT can be a string which may contain the special substrings \"\\&\" for the whole match, \"\\`\" for the part of TARGET-STRING before the match, \"\\'\" for the part of TARGET-STRING after the match, \"\\N\" or \"\\{N}\" for the Nth register where N is a positive integer. REPLACEMENT can also be a function designator in which case the match will be replaced with the result of calling the function designated by REPLACEMENT with the arguments TARGET-STRING, START, END, MATCH-START, MATCH-END, REG-STARTS, and REG-ENDS. (REG-STARTS and REG-ENDS are arrays holding the start and end positions of matched registers or NIL - the meaning of the other arguments should be obvious.) Finally, REPLACEMENT can be a list where each element is a string, one of the symbols :MATCH, :BEFORE-MATCH, or :AFTER-MATCH - corresponding to \"\\&\", \"\\`\", and \"\\'\" above -, an integer N - representing register (1+ N) -, or a function designator. If PRESERVE-CASE is true, the replacement will try to preserve the case (all upper case, all lower case, or capitalized) of the match. The result will always be a fresh string, even if REGEX doesn't match. ELEMENT-TYPE is the element type of the resulting string." (declare #.*standard-optimize-settings*) (let ((pos-list '()) (reg-list '())) (do-scans (match-start match-end reg-starts reg-ends regex target-string nil :start start :end end) (push match-start pos-list) (push match-end pos-list) (push reg-starts reg-list) (push reg-ends reg-list)) (if pos-list (values (replace-aux target-string replacement (nreverse pos-list) (nreverse reg-list) start end preserve-case simple-calls element-type) t) (values (subseq target-string start end) nil)))) #-:cormanlisp (define-compiler-macro regex-replace-all (&whole form &environment env regex target-string replacement &rest rest) "Make sure that constant forms are compiled into scanners at compile time." (cond ((constantp regex env) `(regex-replace-all (load-time-value (create-scanner ,regex)) ,target-string ,replacement ,@rest)) (t form))) #-:cormanlisp (defmacro regex-apropos-aux ((regex packages case-insensitive &optional return-form) &body body) "Auxiliary macro used by REGEX-APROPOS and REGEX-APROPOS-LIST. Loops through PACKAGES and executes BODY with SYMBOL bound to each symbol which matches REGEX. Optionally evaluates and returns RETURN-FORM at the end. If CASE-INSENSITIVE is true and REGEX isn't already a scanner, a case-insensitive scanner is used." (with-rebinding (regex) (with-unique-names (scanner %packages next morep hash) `(let* ((,scanner (create-scanner ,regex :case-insensitive-mode (and ,case-insensitive (not (functionp ,regex))))) (,%packages (or ,packages (list-all-packages))) (,hash (make-hash-table :test #'eq))) (with-package-iterator (,next ,%packages :external :internal :inherited) (loop (multiple-value-bind (,morep symbol) (,next) (unless ,morep (return ,return-form)) (unless (gethash symbol ,hash) (when (scan ,scanner (symbol-name symbol)) (setf (gethash symbol ,hash) t) ,@body))))))))) ;;; The following two functions were provided by Karsten Poeck #+:cormanlisp (defmacro do-with-all-symbols ((variable package-or-packagelist) &body body) "Executes BODY with VARIABLE bound to each symbol in PACKAGE-OR-PACKAGELIST \(a designator for a list of packages) in turn." (with-unique-names (pack-var) `(if (listp ,package-or-packagelist) (dolist (,pack-var ,package-or-packagelist) (do-symbols (,variable ,pack-var) ,@body)) (do-symbols (,variable ,package-or-packagelist) ,@body)))) #+:cormanlisp (defmacro regex-apropos-aux ((regex packages case-insensitive &optional return-form) &body body) "Auxiliary macro used by REGEX-APROPOS and REGEX-APROPOS-LIST. Loops through PACKAGES and executes BODY with SYMBOL bound to each symbol which matches REGEX. Optionally evaluates and returns RETURN-FORM at the end. If CASE-INSENSITIVE is true and REGEX isn't already a scanner, a case-insensitive scanner is used." (with-rebinding (regex) (with-unique-names (scanner %packages hash) `(let* ((,scanner (create-scanner ,regex :case-insensitive-mode (and ,case-insensitive (not (functionp ,regex))))) (,%packages (or ,packages (list-all-packages))) (,hash (make-hash-table :test #'eq))) (do-with-all-symbols (symbol ,%packages) (unless (gethash symbol ,hash) (when (scan ,scanner (symbol-name symbol)) (setf (gethash symbol ,hash) t) ,@body))) ,return-form)))) (defun regex-apropos-list (regex &optional packages &key (case-insensitive t)) (declare #.*standard-optimize-settings*) "Similar to the standard function APROPOS-LIST but returns a list of all symbols which match the regular expression REGEX. If CASE-INSENSITIVE is true and REGEX isn't already a scanner, a case-insensitive scanner is used." (let ((collector '())) (regex-apropos-aux (regex packages case-insensitive collector) (push symbol collector)))) (defun print-symbol-info (symbol) "Auxiliary function used by REGEX-APROPOS. Tries to print some meaningful information about a symbol." (declare #.*standard-optimize-settings*) (handler-case (let ((output-list '())) (cond ((special-operator-p symbol) (push "[special operator]" output-list)) ((macro-function symbol) (push "[macro]" output-list)) ((fboundp symbol) (let* ((function (symbol-function symbol)) (compiledp (compiled-function-p function))) (multiple-value-bind (lambda-expr closurep) (function-lambda-expression function) (push (format nil "[~:[~;compiled ~]~:[function~;closure~]]~:[~; ~A~]" compiledp closurep lambda-expr (cadr lambda-expr)) output-list))))) (let ((class (find-class symbol nil))) (when class (push (format nil "[class] ~S" class) output-list))) (cond ((keywordp symbol) (push "[keyword]" output-list)) ((constantp symbol) (push (format nil "[constant]~:[~; value: ~S~]" (boundp symbol) (symbol-value symbol)) output-list)) ((boundp symbol) (push #+(or :lispworks :clisp) "[variable]" #-(or :lispworks :clisp) (format nil "[variable] value: ~S" (symbol-value symbol)) output-list))) #-(or :cormanlisp :clisp) (format t "~&~S ~<~;~^~A~@{~:@_~A~}~;~:>" symbol output-list) #+(or :cormanlisp :clisp) (loop for line in output-list do (format t "~&~S ~A" symbol line))) (condition () ;; this seems to be necessary due to some errors I encountered ;; with LispWorks (format t "~&~S [an error occurred while trying to print more info]" symbol)))) (defun regex-apropos (regex &optional packages &key (case-insensitive t)) "Similar to the standard function APROPOS but returns a list of all symbols which match the regular expression REGEX. If CASE-INSENSITIVE is true and REGEX isn't already a scanner, a case-insensitive scanner is used." (declare #.*standard-optimize-settings*) (regex-apropos-aux (regex packages case-insensitive) (print-symbol-info symbol)) (values)) (let* ((*use-bmh-matchers* nil) (non-word-char-scanner (create-scanner "[^a-zA-Z_0-9]"))) (defun quote-meta-chars (string &key (start 0) (end (length string))) "Quote, i.e. prefix with #\\\\, all non-word characters in STRING." (regex-replace-all non-word-char-scanner string "\\\\\\&" :start start :end end))) (let* ((*use-bmh-matchers* nil) (*allow-quoting* nil) (quote-char-scanner (create-scanner "\\\\Q")) (section-scanner (create-scanner "\\\\Q((?:[^\\\\]|\\\\(?!Q))*?)(?:\\\\E|$)"))) (defun quote-sections (string) "Replace sections inside of STRING which are enclosed by \\Q and \\E with the quoted equivalent of these sections \(see QUOTE-META-CHARS). Repeat this as long as there are such sections. These sections may nest." (flet ((quote-substring (target-string start end match-start match-end reg-starts reg-ends) (declare (ignore start end match-start match-end)) (quote-meta-chars target-string :start (svref reg-starts 0) :end (svref reg-ends 0)))) (loop for result = string then (regex-replace-all section-scanner result #'quote-substring) while (scan quote-char-scanner result) finally (return result))))) (let* ((*use-bmh-matchers* nil) (comment-scanner (create-scanner "(?s)\\(\\?#.*?\\)")) (extended-comment-scanner (create-scanner "(?m:#.*?$)|(?s:\\(\\?#.*?\\))")) (quote-token-scanner "\\\\[QE]") (quote-token-replace-scanner "\\\\([QE])")) (defun clean-comments (string &optional extended-mode) "Clean \(?#...) comments within STRING for quoting, i.e. convert \\Q to Q and \\E to E. If EXTENDED-MODE is true, also clean end-of-line comments, i.e. those starting with #\\# and ending with #\\Newline." (flet ((remove-tokens (target-string start end match-start match-end reg-starts reg-ends) (declare (ignore start end reg-starts reg-ends)) (loop for result = (nsubseq target-string match-start match-end) then (regex-replace-all quote-token-replace-scanner result "\\1") ;; we must probably repeat this because the comment ;; can contain substrings like \\Q while (scan quote-token-scanner result) finally (return result)))) (regex-replace-all (if extended-mode extended-comment-scanner comment-scanner) string #'remove-tokens)))) (defun parse-tree-synonym (symbol) "Returns the parse tree the SYMBOL symbol is a synonym for. Returns NIL is SYMBOL wasn't yet defined to be a synonym." (get symbol 'parse-tree-synonym)) (defun (setf parse-tree-synonym) (new-parse-tree symbol) "Defines SYMBOL to be a synonm for the parse tree NEW-PARSE-TREE." (setf (get symbol 'parse-tree-synonym) new-parse-tree)) (defmacro define-parse-tree-synonym (name parse-tree) "Defines the symbol NAME to be a synonym for the parse tree PARSE-TREE. Both arguments are quoted." `(eval-when (:compile-toplevel :load-toplevel :execute) (setf (parse-tree-synonym ',name) ',parse-tree))) cl-ppcre-2.0.3/CHANGELOG0000644000175700010010000002437011271772156012670 0ustar ediNoneVersion 2.0.3 2009-10-28 Use LW:SIMPLE-TEXT-STRING throughout for LispWorks Version 2.0.2 2009-09-17 Fixed typo in chartest.lisp (caught by Peter Seibel) Appease CCL (thanks to Hans Hübner) Version 2.0.1 2008-09-02 Fixed faulty declaration (caught by Brent Fulgham) Version 2.0.0 2008-07-24 Added named properties (\p{foo}) Added Unicode support Introduced test functions for character classes Added optional test function optimization Cleaned up test suite, removed performance cruft Removed the various alternative system definitions (too much maintenance work) Exported PARSE-STRING Changed default value of *USE-BMH-MATCHERS* General cleanup Lots of documentation additions Version 1.4.1 2008-07-03 Skip non-characters in CREATE-RANGES-FROM-SET Version 1.4.0 2008-07-03 Replaced hash tables with charsets (by Nikodemus Siivola) Get rid of duplicates in REGEX-APROPOS(-LIST) Version 1.3.3 2008-06-25 Let the Lisp decide how it wants to enlarge its hash tables Fixed anchors for special variables in docs Fixed typo in docs (thanks to Jason S. Cornez) Version 1.3.2 2007-09-13 Updated docs and ChangeLog to be really in sync with 1.3.1 changes (thanks to Sébastien Saint-Sevin) Version 1.3.1 2007-08-24 Second return value for REGEX-REPLACE and REGEX-REPLACE-ALL (patch by Matthew Sachs) Version 1.3.0 2007-03-24 Optional support for named registers (patch by Ondrej Svitek) Version 1.2.19 2007-01-16 Fixed behaviour of look-behind in repeated scans (caught by RegexCoach user Hans Jud) Version 1.2.18 2006-10-12 Changed default element type for LispWorks Fixed documentation for REGEX-REPLACE-ALL Version 1.2.17 2006-10-11 Fixed bug in DO-SCANS which affected anchors (caught by RegexCoach user Laurent Taupiac) Update link for 'man perlre' (thanks to Ricardo Boccato Alves) Version 1.2.16 2006-07-16 Added :ELEMENT-TYPE to REGEX-REPLACE(-ALL) Version 1.2.15 2006-07-03 Added :REGEX tag to parse tree syntax (thanks to Frédéric Jolliton) Version 1.2.14 2006-05-24 Added missing tag in docs (thanks to Wojciech Kaczmarek) Fixed IMPORT statement for LW Version 1.2.13 2005-12-06 Fixed bug involving *REAL-START-POS* (caught by "tichy") Version 1.2.12 2005-11-01 REGEX-APROPOS-AUX now also uses :INHERITED Fixed typo in parser.lisp (thanks to Derek Peschel) Fixed value of *REGEX-CHAR-CODE-LIMIT* in docs and test (thanks to Christophe Rhodes) Version 1.2.11 2005-08-01 Added external format for SBCL in ppcre-tests.lisp (thanks to Christophe Rhodes) Version 1.2.10 2005-07-20 Fixed bug in CHAR-SEARCHER-AUX (caught by Peter Schuller) Don't redefine what's already there (for LispWorks) Version 1.2.9 2005-06-27 Hide compiler macros from CCL (thanks to Karsten Poeck) Version 1.2.8 2005-06-10 Change EQ to EQL in REGEX-LENGTH for ANSI conformance and ABCL compatibility (thanks to Peter Graves) Version 1.2.7 2005-05-16 Added lispworks-defsystem.lisp (thanks to Wade Humeniuk) Fixed bug in WORD-BOUNDARY-P Version 1.2.6 2005-04-13 Added some DEFGENERICs to appease SBCL (thanks to Alan Shields) Removed wrong FTYPE declaration for STR (thanks to Alan Shields) Version 1.2.5 2005-03-09 Customizable optimize qualities (thanks to Damien Kick) Version 1.2.4 2005-03-07 Changed DEBUG optimize quality from 0 to 1 Version 1.2.3 2005-02-02 Wrapped WITH-COMPILATION-UNIT around loop in load.lisp Version 1.2.2 2005-02-02 Fixed bug in hash table optimization (introduced in 1.1.0) Version 1.2.1 2005-01-25 There was a wrong read-time conditional in api.lisp, sorry Version 1.2.0 2005-01-24 AllegroCL compatibility mode Fixed broken load.lisp file (caught by Jim Prewett and Zach Beane) Version 1.1.0 2005-01-23 Cleaned up load.lisp and cl-ppcre.asd Make large hash tables smaller, if possible Correct treatment of constant regular expressions in DO-SCANS Version 1.0.0 2004-12-22 Special anniversary release... :) Version 0.9.4 2004-12-18 Fixed bug in NORMALIZE-VAR-LIST (caught by Dave Roberts) Version 0.9.3 2004-12-09 Fixed bug in CREATE-SCANNER-AUX (caught by Allan Ruttenberg and Gary Byers) Version 0.9.2 2004-12-06 More compiler macros (thanks to Allan Ruttenberg) Version 0.9.1 2004-11-29 Shortcuts for REGISTER-GROUPS-BIND and DO-REGISTER-GROUPS (suggested by Alexander Kjeldaas) Version 0.9.0 2004-10-14 Experimental support for "filters" Bugfix for standalone regular expressions (ACCUMULATE-START-P wasn't set to NIL) Version 0.8.1 2004-09-30 Patches for Genera 8.5 (thanks to Patrick O'Donnell) Version 0.8.0 2004-09-16 Added parse tree synonyms (thanks to Patrick O'Donnell) Version 0.7.9 2004-07-13 Fixed bug in DO-SCANS (caught by Jan Rychter) Version 0.7.8 2004-07-13 New SIMPLE-CALLS keyword argument for REGEX-REPLACE(-ALL) Added environment parameter to compiler macros (thanks to c.l.l article by Joe Marshall) Added compiler macros for SCAN-TO-STRINGS and REGEX-REPLACE(-ALL) (they somehow got lost) Version 0.7.7 2004-05-19 Fixed bug in NEWLINE-SKIPPER (caught by RegexCoach user Thomas-Paz Hartman) Added doc strings for PPCRE-SYNTAX-ERROR and friends (after playing with slime-apropos-package) Added hyperdoc support Version 0.7.6 2004-04-20 The closures created by CREATE-BMH-MATCHER now cleanly cope with negative arguments (bug caught by Damien Kick) Version 0.7.5 2004-04-19 Fixed a bug with constant-length repetitions of . (dot) in single-line mode (caught by RegexCoach user Lee Gold) Version 0.7.4 2004-02-16 Fixed wrong call to SIGNAL-PPCRE-SIGNAL-ERROR in lexer.lisp (caught by Peter Graves) Added :CL-PPCRE to *FEATURES* (for CL-INTERPOL) Compiler macro for SPLIT Version 0.7.3 2004-01-28 Fixed bug in CURRENT-MIN-REST for lookaheads (reported by RegexCoach user Thomas-Paz Hartman) Added tests for this bug Version 0.7.2 2004-01-27 Fixed typo (SUBSEQ/NSUBSEQ) in SPLIT (thanks to Alan Ruttenberg) Updated docs with respect to ECL (thanks to Alex Mizrahi) Mention FreeBSD port in docs Version 0.7.1 2003-10-24 Fixed version numbers in docs (thanks to Sébastien Saint-Sevin) Version 0.7.0 2003-10-23 New macros REGISTER-GROUPS-BIND and DO-REGISTER-GROUPS Added SHAREP keyword argument to most API functions and macros Mention CL-INTERPOL in docs Partial code cleanup (using WITH-UNIQUE-NAMES and REBINDING) Version 0.6.1 2003-10-11 Added EXTERNAL-FORMAT keyword args to CL-PPCRE-TEST:TEST for some CLs (thanks to JP Massar and Scott D. Kalter) Fixed bug with REGEX-REPLACE and REGEX-REPLACE-ALL when (= START END) was true Added doc sections for quoting problems and backslash confusions (thanks to conversations with Peter Seibel) Disable quoting in definition of QUOTE-SECTIONS so you can always safely rebuild CL-PPCRE Version 0.6.0 2003-10-07 CL-PPCRE now has its own condition types Added support for Perl's \Q and \E (Peter Seibel convinced me to do it) - see QUOTE-META-CHARS and *ALLOW-QUOTING* Added tests for this new feature Threaded tests are more verbose now and use only keyword args Version 0.5.9 2003-10-03 Changed "^" optimizations with respect to constant end strings with offsets (bug caught by Yexuan Gui) Added tests for this bug Removed *.dos files from CL-PPCRE-TEST tests (thanks to JP Massar) Added threaded tests for SBCL (thanks to Christophe Rhodes) Version 0.5.8 2003-09-17 Optimizations for ".*" were too optimistic when look-behinds were involved Added tests for this bug Removed *.dos files Version 0.5.7 2003-08-20 Fixed (CL-PPCRE:SCAN "(.)X$" "ABCX" :START 4) bug (spotted by Tibor Simko) Forgot to export *REGEX-CHAR-CODE-LIMIT* in Corman version of DEFPACKAGE Removed Emacs local variables from source code (finally...) Mention Gentoo in docs Version 0.5.6 2003-06-30 Replaced wrong COPY-REGEX code for WORD-BOUNDARY objects (detected by Max Goldberg) Added info about possible TRUENAME problems with ACL in README (thanks to Kevin Layer for providing a patch for this) Version 0.5.5 2003-06-09 Patch for SBCL/Debian compatibility by Kevin Rosenberg Simpler version of compiler macro Availability through asdf-install Version 0.5.4 2003-04-09 Added DESTRUCTIVE keyword to CREATE-SCANNER Version 0.5.3 2003-03-31 Fixed bug in REGEX-REPLACE (replacement string couldn't contain literal backslash) Fixed bug in definition of CHAR-CLASS (since 0.5.0 the hash slot may be NIL - CMUCL's new PCL detects this) Micro-optimization in INSERT-CHAR-CLASS-TESTER: CHAR-NOT-GREATERP instead of CHAR-DOWNCASE Version 0.5.2 2003-03-28 Better compiler macro (thanks to Kent M. Pitman) Version 0.5.1 2003-03-27 Removed compiler macro Version 0.5.0 2003-03-27 Lexer, parser, and converter mostly re-written to reduce consing and increase speed Get rid of FIX-POS in lexer and parser, "ism" flags are handled after parsing now Smaller test suite (again) due to literal embedding of line breaks Seperate test files for DOS line endings Replaced constant +REGEX-CHAR-CODE-LIMIT+ with special variable *REGEX-CHAR-CODE-LIMIT* Version 0.4.1 2003-03-19 Added compiler macro for SCAN Changed test suite to be nicer to Corman Lisp and ECL (see docs for new syntax) Incorporated visual feedback (dots) in test suite (thanks to JP Massar) Added README file Replaced STRING-LIST-TO-SIMPLE-STRING with a much improved version by JP Massar Version 0.4.0 2003-02-27 Added *USE-BMH-MATCHER* Version 0.3.2 2003-02-21 Added load.lisp Various minor changes for Corman Lisp compatibility (thanks to Karsten Poeck and JP Massar) Version 0.3.1 2003-01-18 Bugfix in CREATE-SCANNER (didn't work if flags were given and arg was a parse-tree) Version 0.3.0 2003-01-12 Added new features to REGEX-REPLACE and REGEX-REPLACE-ALL Version 0.2.0 2003-01-11 Make SPLIT more Perl-compatible, including new keyword parameters Version 0.1.4 2003-01-10 Don't move "^" and "\A" while iterating with DO-SCANS Added link to Debian package Version 0.1.3 2002-12-25 More usable MK:DEFSYSTEM files (courtesy of Hannu Koivisto) Fixed typo in documentation Version 0.1.2 2002-12-22 Added version numbers for Debian packaging Be friendly to case-sensitive ACL images (courtesy of Kevin Rosenberg and Douglas Crosher) "Fixed" two cases where declarations came after docstrings (because of bugs in Corman Lisp and older CMUCL versions) Added #-cormanlisp to hide (INCF (THE FIXNUM POS)) from Corman Lisp Added file doc/benchmarks.2002-12-22.txt Version 0.1.1 2002-12-21 Added asdf system definitions by Marco Baringer Small additions to documentation Correct (Emacs) local variables list in closures.lisp and api.lisp Added this CHANGELOG Version 0.1.0 2002-12-20 Initial release cl-ppcre-2.0.3/charmap.lisp0000644000175700010010000001545511254505512013755 0ustar ediNone;;; -*- Mode: LISP; Syntax: COMMON-LISP; Package: CL-PPCRE; Base: 10 -*- ;;; $Header: /usr/local/cvsrep/cl-ppcre/charmap.lisp,v 1.19 2009/09/17 19:17:30 edi Exp $ ;;; An optimized representation of sets of characters. ;;; Copyright (c) 2008-2009, Dr. Edmund Weitz. All rights reserved. ;;; Redistribution and use in source and binary forms, with or without ;;; modification, are permitted provided that the following conditions ;;; are met: ;;; * Redistributions of source code must retain the above copyright ;;; notice, this list of conditions and the following disclaimer. ;;; * Redistributions in binary form must reproduce the above ;;; copyright notice, this list of conditions and the following ;;; disclaimer in the documentation and/or other materials ;;; provided with the distribution. ;;; THIS SOFTWARE IS PROVIDED BY THE AUTHOR 'AS IS' AND ANY EXPRESSED ;;; OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED ;;; WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ;;; ARE DISCLAIMED. IN NO EVENT SHALL THE AUTHOR BE LIABLE FOR ANY ;;; DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL ;;; DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE ;;; GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS ;;; INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, ;;; WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING ;;; NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE OF THIS ;;; SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. (in-package :cl-ppcre) (defstruct (charmap (:constructor make-charmap%)) ;; a bit vector mapping char codes to "booleans" (1 for set members, ;; 0 for others) (vector #*0 :type simple-bit-vector) ;; the smallest character code of all characters in the set (start 0 :type fixnum) ;; the upper (exclusive) bound of all character codes in the set (end 0 :type fixnum) ;; the number of characters in the set, or NIL if this is unknown (count nil :type (or fixnum null)) ;; whether the charmap actually represents the complement of the set (complementp nil :type boolean)) ;; seems to be necessary for some Lisps like ClozureCL (defmethod make-load-form ((map charmap) &optional environment) (make-load-form-saving-slots map :environment environment)) (declaim (inline in-charmap-p)) (defun in-charmap-p (char charmap) "Tests whether the character CHAR belongs to the set represented by CHARMAP." (declare #.*standard-optimize-settings*) (declare (character char) (charmap charmap)) (let* ((char-code (char-code char)) (char-in-vector-p (let ((charmap-start (charmap-start charmap))) (declare (fixnum charmap-start)) (and (<= charmap-start char-code) (< char-code (the fixnum (charmap-end charmap))) (= 1 (sbit (the simple-bit-vector (charmap-vector charmap)) (- char-code charmap-start))))))) (cond ((charmap-complementp charmap) (not char-in-vector-p)) (t char-in-vector-p)))) (defun charmap-contents (charmap) "Returns a list of all characters belonging to a character map. Only works for non-complement charmaps." (declare #.*standard-optimize-settings*) (declare (charmap charmap)) (and (not (charmap-complementp charmap)) (loop for code of-type fixnum from (charmap-start charmap) to (charmap-end charmap) for i across (the simple-bit-vector (charmap-vector charmap)) when (= i 1) collect (code-char code)))) (defun make-charmap (start end test-function &optional complementp) "Creates and returns a charmap representing all characters with character codes in the interval [start end) that satisfy TEST-FUNCTION. The COMPLEMENTP slot of the charmap is set to the value of the optional argument, but this argument doesn't have an effect on how TEST-FUNCTION is used." (declare #.*standard-optimize-settings*) (declare (fixnum start end)) (let ((vector (make-array (- end start) :element-type 'bit)) (count 0)) (declare (fixnum count)) (loop for code from start below end for char = (code-char code) for index from 0 when char do (incf count) (setf (sbit vector index) (if (funcall test-function char) 1 0))) (make-charmap% :vector vector :start start :end end ;; we don't know for sure if COMPLEMENTP is true as ;; there isn't a necessary a character for each ;; integer below *REGEX-CHAR-CODE-LIMIT* :count (and (not complementp) count) ;; make sure it's boolean :complementp (not (not complementp))))) (defun create-charmap-from-test-function (test-function start end) "Creates and returns a charmap representing all characters with character codes between START and END which satisfy TEST-FUNCTION. Tries to find the smallest interval which is necessary to represent the character set and uses the complement representation if that helps." (declare #.*standard-optimize-settings*) (let (start-in end-in start-out end-out) ;; determine the smallest intervals containing the set and its ;; complement, [start-in, end-in) and [start-out, end-out) - first ;; the lower bound (loop for code from start below end for char = (code-char code) until (and start-in start-out) when (and char (not start-in) (funcall test-function char)) do (setq start-in code) when (and char (not start-out) (not (funcall test-function char))) do (setq start-out code)) (unless start-in ;; no character satisfied the test, so return a "pseudo" charmap ;; where IN-CHARMAP-P is always false (return-from create-charmap-from-test-function (make-charmap% :count 0))) (unless start-out ;; no character failed the test, so return a "pseudo" charmap ;; where IN-CHARMAP-P is always true (return-from create-charmap-from-test-function (make-charmap% :complementp t))) ;; now determine upper bound (loop for code from (1- end) downto start for char = (code-char code) until (and end-in end-out) when (and char (not end-in) (funcall test-function char)) do (setq end-in (1+ code)) when (and char (not end-out) (not (funcall test-function char))) do (setq end-out (1+ code))) ;; use the smaller interval (cond ((<= (- end-in start-in) (- end-out start-out)) (make-charmap start-in end-in test-function)) (t (make-charmap start-out end-out (complement* test-function) t))))) cl-ppcre-2.0.3/charset.lisp0000644000175700010010000002415211254505512013765 0ustar ediNone;;; -*- Mode: LISP; Syntax: COMMON-LISP; Package: CL-PPCRE; Base: 10 -*- ;;; $Header: /usr/local/cvsrep/cl-ppcre/charset.lisp,v 1.10 2009/09/17 19:17:30 edi Exp $ ;;; A specialized set implementation for characters by Nikodemus Siivola. ;;; Copyright (c) 2008, Nikodemus Siivola. All rights reserved. ;;; Copyright (c) 2008-2009, Dr. Edmund Weitz. All rights reserved. ;;; Redistribution and use in source and binary forms, with or without ;;; modification, are permitted provided that the following conditions ;;; are met: ;;; * Redistributions of source code must retain the above copyright ;;; notice, this list of conditions and the following disclaimer. ;;; * Redistributions in binary form must reproduce the above ;;; copyright notice, this list of conditions and the following ;;; disclaimer in the documentation and/or other materials ;;; provided with the distribution. ;;; THIS SOFTWARE IS PROVIDED BY THE AUTHOR 'AS IS' AND ANY EXPRESSED ;;; OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED ;;; WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ;;; ARE DISCLAIMED. IN NO EVENT SHALL THE AUTHOR BE LIABLE FOR ANY ;;; DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL ;;; DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE ;;; GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS ;;; INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, ;;; WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING ;;; NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE OF THIS ;;; SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. (in-package :cl-ppcre) (defconstant +probe-depth+ 3 "Maximum number of collisions \(for any element) we accept before we allocate more storage. This is now fixed, but could be made to vary depending on the size of the storage vector \(e.g. in the range of 1-4). Larger probe-depths mean more collisions are tolerated before the table grows, but increase the constant factor.") (defun make-char-vector (size) "Returns a vector of size SIZE to hold characters. All elements are initialized to #\Null except for the first one which is initialized to #\?." (declare #.*standard-optimize-settings*) (declare (type (integer 2 #.(1- array-total-size-limit)) size)) ;; since #\Null always hashes to 0, store something else there ;; initially, and #\Null everywhere else (let ((result (make-array size :element-type #-:lispworks 'character #+:lispworks 'lw:simple-char :initial-element (code-char 0)))) (setf (char result 0) #\?) result)) (defstruct (charset (:constructor make-charset ())) ;; this is set to 0 when we stop hashing and just use a CHAR-CODE ;; indexed vector (depth +probe-depth+ :type fixnum) ;; the number of characters in this set (count 0 :type fixnum) ;; the storage vector (vector (make-char-vector 12) :type (simple-array character (*)))) ;; seems to be necessary for some Lisps like ClozureCL (defmethod make-load-form ((set charset) &optional environment) (make-load-form-saving-slots set :environment environment)) (declaim (inline mix)) (defun mix (code hash) "Given a character code CODE and a hash code HASH, computes and returns the \"next\" hash code. See comments below." (declare #.*standard-optimize-settings*) ;; mixing the CHAR-CODE back in at each step makes sure that if two ;; characters collide (their hashes end up pointing in the same ;; storage vector index) on one round, they should (hopefully!) not ;; collide on the next (sxhash (logand most-positive-fixnum (+ code hash)))) (declaim (inline compute-index)) (defun compute-index (hash vector) "Computes and returns the index into the vector VECTOR corresponding to the hash code HASH." (declare #.*standard-optimize-settings*) (1+ (mod hash (1- (length vector))))) (defun in-charset-p (char set) "Checks whether the character CHAR is in the charset SET." (declare #.*standard-optimize-settings*) (declare (character char) (charset set)) (let ((vector (charset-vector set)) (depth (charset-depth set)) (code (char-code char))) (declare (fixnum depth)) ;; as long as the set remains reasonably small, we use non-linear ;; hashing - the first hash of any character is its CHAR-CODE, and ;; subsequent hashes are computed by MIX above (cond ((or ;; depth 0 is special - each char maps only to its code, ;; nothing else (zerop depth) ;; index 0 is special - only #\Null maps to it, no matter ;; what the depth is (zerop code)) (eq char (char vector code))) (t ;; otherwise hash starts out as the character code, but ;; maps to indexes 1-N (let ((hash code)) (tagbody :retry (let* ((index (compute-index hash vector)) (x (char vector index))) (cond ((eq x (code-char 0)) ;; empty, no need to probe further (return-from in-charset-p nil)) ((eq x char) ;; got it (return-from in-charset-p t)) ((zerop (decf depth)) ;; max probe depth reached, nothing found (return-from in-charset-p nil)) (t ;; nothing yet, try next place (setf hash (mix code hash)) (go :retry)))))))))) (defun add-to-charset (char set) "Adds the character CHAR to the charset SET, extending SET if necessary. Returns CHAR." (declare #.*standard-optimize-settings*) (or (%add-to-charset char set t) (%add-to-charset/expand char set) (error "Oops, this should not happen...")) char) (defun %add-to-charset (char set count) "Tries to add the character CHAR to the charset SET without extending it. Returns NIL if this fails. Counts CHAR as new if COUNT is true and it is added to SET." (declare #.*standard-optimize-settings*) (declare (character char) (charset set)) (let ((vector (charset-vector set)) (depth (charset-depth set)) (code (char-code char))) (declare (fixnum depth)) ;; see comments in IN-CHARSET-P for algorithm (cond ((or (zerop depth) (zerop code)) (unless (eq char (char vector code)) (setf (char vector code) char) (when count (incf (charset-count set)))) char) (t (let ((hash code)) (tagbody :retry (let* ((index (compute-index hash vector)) (x (char vector index))) (cond ((eq x (code-char 0)) (setf (char vector index) char) (when count (incf (charset-count set))) (return-from %add-to-charset char)) ((eq x char) (return-from %add-to-charset char)) ((zerop (decf depth)) ;; need to expand the table (return-from %add-to-charset nil)) (t (setf hash (mix code hash)) (go :retry)))))))))) (defun %add-to-charset/expand (char set) "Extends the charset SET and then adds the character CHAR to it." (declare #.*standard-optimize-settings*) (declare (character char) (charset set)) (let* ((old-vector (charset-vector set)) (new-size (* 2 (length old-vector)))) (tagbody :retry ;; when the table grows large (currently over 1/3 of ;; CHAR-CODE-LIMIT), we dispense with hashing and just allocate a ;; storage vector with space for all characters, so that each ;; character always uses only the CHAR-CODE (multiple-value-bind (new-depth new-vector) (if (>= new-size #.(truncate char-code-limit 3)) (values 0 (make-char-vector char-code-limit)) (values +probe-depth+ (make-char-vector new-size))) (setf (charset-depth set) new-depth (charset-vector set) new-vector) (flet ((try-add (x) ;; don't count - old characters are already accounted ;; for, and might count the new one multiple times as ;; well (unless (%add-to-charset x set nil) (assert (not (zerop new-depth))) (setf new-size (* 2 new-size)) (go :retry)))) (try-add char) (dotimes (i (length old-vector)) (let ((x (char old-vector i))) (if (eq x (code-char 0)) (when (zerop i) (try-add x)) (unless (zerop i) (try-add x)))))))) ;; added and expanded, /now/ count the new character. (incf (charset-count set)) t)) (defun map-charset (function charset) "Calls FUNCTION with all characters in SET. Returns NIL." (declare #.*standard-optimize-settings*) (declare (function function)) (let* ((n (charset-count charset)) (vector (charset-vector charset)) (size (length vector))) ;; see comments in IN-CHARSET-P for algorithm (when (eq (code-char 0) (char vector 0)) (funcall function (code-char 0)) (decf n)) (loop for i from 1 below size for char = (char vector i) unless (eq (code-char 0) char) do (funcall function char) ;; this early termination test should be worth it when ;; mapping across depth 0 charsets. (when (zerop (decf n)) (return-from map-charset nil)))) nil) (defun create-charset-from-test-function (test-function start end) "Creates and returns a charset representing all characters with character codes between START and END which satisfy TEST-FUNCTION." (declare #.*standard-optimize-settings*) (loop with charset = (make-charset) for code from start below end for char = (code-char code) when (and char (funcall test-function char)) do (add-to-charset char charset) finally (return charset))) cl-ppcre-2.0.3/chartest.lisp0000755000175700010010000001164611254505512014160 0ustar ediNone;;; -*- Mode: LISP; Syntax: COMMON-LISP; Package: CL-PPCRE; Base: 10 -*- ;;; $Header: /usr/local/cvsrep/cl-ppcre/chartest.lisp,v 1.5 2009/09/17 19:17:30 edi Exp $ ;;; Copyright (c) 2008-2009, Dr. Edmund Weitz. All rights reserved. ;;; Redistribution and use in source and binary forms, with or without ;;; modification, are permitted provided that the following conditions ;;; are met: ;;; * Redistributions of source code must retain the above copyright ;;; notice, this list of conditions and the following disclaimer. ;;; * Redistributions in binary form must reproduce the above ;;; copyright notice, this list of conditions and the following ;;; disclaimer in the documentation and/or other materials ;;; provided with the distribution. ;;; THIS SOFTWARE IS PROVIDED BY THE AUTHOR 'AS IS' AND ANY EXPRESSED ;;; OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED ;;; WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ;;; ARE DISCLAIMED. IN NO EVENT SHALL THE AUTHOR BE LIABLE FOR ANY ;;; DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL ;;; DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE ;;; GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS ;;; INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, ;;; WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING ;;; NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE OF THIS ;;; SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. (in-package :cl-ppcre) (defun create-hash-table-from-test-function (test-function start end) "Creates and returns a hash table representing all characters with character codes between START and END which satisfy TEST-FUNCTION." (declare #.*standard-optimize-settings*) (loop with hash-table = (make-hash-table) for code from start below end for char = (code-char code) when (and char (funcall test-function char)) do (setf (gethash char hash-table) t) finally (return hash-table))) (defun create-optimized-test-function (test-function &key (start 0) (end *regex-char-code-limit*) (kind *optimize-char-classes*)) "Given a unary test function which is applicable to characters returns a function which yields the same boolean results for all characters with character codes from START to \(excluding) END. If KIND is NIL, TEST-FUNCTION will simply be returned. Otherwise, KIND should be one of: * :HASH-TABLE - builds a hash table representing all characters which satisfy the test and returns a closure which checks if a character is in that hash table * :CHARSET - instead of a hash table uses a \"charset\" which is a data structure using non-linear hashing and optimized to represent \(sparse) sets of characters in a fast and space-efficient way \(contributed by Nikodemus Siivola) * :CHARMAP - instead of a hash table uses a bit vector to represent the set of characters You can also use :HASH-TABLE* or :CHARSET* which are like :HASH-TABLE and :CHARSET but use the complement of the set if the set contains more than half of all characters between START and END. This saves space but needs an additional pass across all characters to create the data structure. There is no corresponding :CHARMAP* kind as the bit vectors are already created to cover the smallest possible interval which contains either the set or its complement." (declare #.*standard-optimize-settings*) (ecase kind ((nil) test-function) (:charmap (let ((charmap (create-charmap-from-test-function test-function start end))) (lambda (char) (in-charmap-p char charmap)))) ((:charset :charset*) (let ((charset (create-charset-from-test-function test-function start end))) (cond ((or (eq kind :charset) (<= (charset-count charset) (ceiling (- end start) 2))) (lambda (char) (in-charset-p char charset))) (t (setq charset (create-charset-from-test-function (complement* test-function) start end)) (lambda (char) (not (in-charset-p char charset))))))) ((:hash-table :hash-table*) (let ((hash-table (create-hash-table-from-test-function test-function start end))) (cond ((or (eq kind :hash-table) (<= (hash-table-count hash-table) (ceiling (- end start) 2))) (lambda (char) (gethash char hash-table))) (t (setq hash-table (create-hash-table-from-test-function (complement* test-function) start end)) (lambda (char) (not (gethash char hash-table))))))))) cl-ppcre-2.0.3/cl-ppcre-unicode/0000755000175700010010000000000011271772245014600 5ustar ediNonecl-ppcre-2.0.3/cl-ppcre-unicode/packages.lisp0000644000175700010010000000344111254505516017245 0ustar ediNone;;; -*- Mode: LISP; Syntax: COMMON-LISP; Package: CL-USER; Base: 10 -*- ;;; $Header: /usr/local/cvsrep/cl-ppcre/cl-ppcre-unicode/packages.lisp,v 1.3 2009/09/17 19:17:34 edi Exp $ ;;; Copyright (c) 2002-2009, Dr. Edmund Weitz. All rights reserved. ;;; Redistribution and use in source and binary forms, with or without ;;; modification, are permitted provided that the following conditions ;;; are met: ;;; * Redistributions of source code must retain the above copyright ;;; notice, this list of conditions and the following disclaimer. ;;; * Redistributions in binary form must reproduce the above ;;; copyright notice, this list of conditions and the following ;;; disclaimer in the documentation and/or other materials ;;; provided with the distribution. ;;; THIS SOFTWARE IS PROVIDED BY THE AUTHOR 'AS IS' AND ANY EXPRESSED ;;; OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED ;;; WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ;;; ARE DISCLAIMED. IN NO EVENT SHALL THE AUTHOR BE LIABLE FOR ANY ;;; DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL ;;; DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE ;;; GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS ;;; INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, ;;; WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING ;;; NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE OF THIS ;;; SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. (in-package :cl-user) (defpackage :cl-ppcre-unicode #+:genera (:shadowing-import-from :common-lisp :lambda :string) (:use #-:genera :cl #+:genera :future-common-lisp :cl-ppcre :cl-unicode) (:import-from :cl-ppcre :signal-syntax-error) (:export :unicode-property-resolver)) cl-ppcre-2.0.3/cl-ppcre-unicode/resolver.lisp0000644000175700010010000000523711041511760017325 0ustar ediNone;;; -*- Mode: LISP; Syntax: COMMON-LISP; Package: CL-PPCRE; Base: 10 -*- ;;; $Header: /usr/local/cvsrep/cl-ppcre/cl-ppcre-unicode/resolver.lisp,v 1.5 2008/07/23 02:14:08 edi Exp $ ;;; Copyright (c) 2008, Dr. Edmund Weitz. All rights reserved. ;;; Redistribution and use in source and binary forms, with or without ;;; modification, are permitted provided that the following conditions ;;; are met: ;;; * Redistributions of source code must retain the above copyright ;;; notice, this list of conditions and the following disclaimer. ;;; * Redistributions in binary form must reproduce the above ;;; copyright notice, this list of conditions and the following ;;; disclaimer in the documentation and/or other materials ;;; provided with the distribution. ;;; THIS SOFTWARE IS PROVIDED BY THE AUTHOR 'AS IS' AND ANY EXPRESSED ;;; OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED ;;; WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ;;; ARE DISCLAIMED. IN NO EVENT SHALL THE AUTHOR BE LIABLE FOR ANY ;;; DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL ;;; DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE ;;; GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS ;;; INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, ;;; WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING ;;; NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE OF THIS ;;; SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. (in-package :cl-ppcre-unicode) (defun unicode-property-resolver (property-name) "A property resolver which understands Unicode properties using CL-UNICODE's PROPERTY-TEST function. This resolver is automatically installed in *PROPERTY-RESOLVER* when the CL-PPCRE-UNICODE system is loaded." (or (property-test property-name :errorp nil) (signal-syntax-error "There is no property named ~S." property-name))) (setq *property-resolver* 'unicode-property-resolver) (pushnew :cl-ppcre-unicode *features*) ;; stuff for Nikodemus Siivola's HYPERDOC ;; see ;; and ;; also used by LW-ADD-ONS (defvar *hyperdoc-base-uri* "http://weitz.de/cl-ppcre/") (let ((exported-symbols-alist (loop for symbol being the external-symbols of :cl-ppcre-unicode collect (cons symbol (concatenate 'string "#" (string-downcase symbol)))))) (defun hyperdoc-lookup (symbol type) (declare (ignore type)) (cdr (assoc symbol exported-symbols-alist :test #'eq)))) cl-ppcre-2.0.3/cl-ppcre-unicode.asd0000644000175700010010000000504411254505512015264 0ustar ediNone;;; -*- Mode: LISP; Syntax: COMMON-LISP; Package: CL-USER; Base: 10 -*- ;;; $Header: /usr/local/cvsrep/cl-ppcre/cl-ppcre-unicode.asd,v 1.15 2009/09/17 19:17:30 edi Exp $ ;;; This ASDF system definition was kindly provided by Marco Baringer. ;;; Copyright (c) 2002-2009, Dr. Edmund Weitz. All rights reserved. ;;; Redistribution and use in source and binary forms, with or without ;;; modification, are permitted provided that the following conditions ;;; are met: ;;; * Redistributions of source code must retain the above copyright ;;; notice, this list of conditions and the following disclaimer. ;;; * Redistributions in binary form must reproduce the above ;;; copyright notice, this list of conditions and the following ;;; disclaimer in the documentation and/or other materials ;;; provided with the distribution. ;;; THIS SOFTWARE IS PROVIDED BY THE AUTHOR 'AS IS' AND ANY EXPRESSED ;;; OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED ;;; WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ;;; ARE DISCLAIMED. IN NO EVENT SHALL THE AUTHOR BE LIABLE FOR ANY ;;; DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL ;;; DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE ;;; GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS ;;; INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, ;;; WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING ;;; NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE OF THIS ;;; SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. (in-package :cl-user) (defpackage :cl-ppcre-unicode-asd (:use :cl :asdf)) (in-package :cl-ppcre-unicode-asd) (defsystem :cl-ppcre-unicode :components ((:module "cl-ppcre-unicode" :serial t :components ((:file "packages") (:file "resolver")))) :depends-on (:cl-ppcre :cl-unicode)) (defsystem :cl-ppcre-unicode-test :depends-on (:cl-ppcre-unicode :cl-ppcre-test) :components ((:module "test" :serial t :components ((:file "unicode-tests"))))) (defmethod perform ((o test-op) (c (eql (find-system :cl-ppcre-unicode)))) ;; we must load CL-PPCRE explicitly so that the CL-PPCRE-TEST system ;; will be found (operate 'load-op :cl-ppcre) (operate 'load-op :cl-ppcre-unicode-test) (funcall (intern (symbol-name :run-all-tests) (find-package :cl-ppcre-test)) :more-tests (intern (symbol-name :unicode-test) (find-package :cl-ppcre-test))))cl-ppcre-2.0.3/cl-ppcre.asd0000644000175700010010000000615311271772157013654 0ustar ediNone;;; -*- Mode: LISP; Syntax: COMMON-LISP; Package: CL-USER; Base: 10 -*- ;;; $Header: /usr/local/cvsrep/cl-ppcre/cl-ppcre.asd,v 1.49 2009/10/28 07:36:15 edi Exp $ ;;; This ASDF system definition was kindly provided by Marco Baringer. ;;; Copyright (c) 2002-2009, Dr. Edmund Weitz. All rights reserved. ;;; Redistribution and use in source and binary forms, with or without ;;; modification, are permitted provided that the following conditions ;;; are met: ;;; * Redistributions of source code must retain the above copyright ;;; notice, this list of conditions and the following disclaimer. ;;; * Redistributions in binary form must reproduce the above ;;; copyright notice, this list of conditions and the following ;;; disclaimer in the documentation and/or other materials ;;; provided with the distribution. ;;; THIS SOFTWARE IS PROVIDED BY THE AUTHOR 'AS IS' AND ANY EXPRESSED ;;; OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED ;;; WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ;;; ARE DISCLAIMED. IN NO EVENT SHALL THE AUTHOR BE LIABLE FOR ANY ;;; DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL ;;; DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE ;;; GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS ;;; INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, ;;; WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING ;;; NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE OF THIS ;;; SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. (in-package :cl-user) (defpackage :cl-ppcre-asd (:use :cl :asdf)) (in-package :cl-ppcre-asd) (defsystem :cl-ppcre :version "2.0.3" :serial t :components ((:file "packages") (:file "specials") (:file "util") (:file "errors") (:file "charset") (:file "charmap") (:file "chartest") #-:use-acl-regexp2-engine (:file "lexer") #-:use-acl-regexp2-engine (:file "parser") #-:use-acl-regexp2-engine (:file "regex-class") #-:use-acl-regexp2-engine (:file "regex-class-util") #-:use-acl-regexp2-engine (:file "convert") #-:use-acl-regexp2-engine (:file "optimize") #-:use-acl-regexp2-engine (:file "closures") #-:use-acl-regexp2-engine (:file "repetition-closures") #-:use-acl-regexp2-engine (:file "scanner") (:file "api"))) (defsystem :cl-ppcre-test :depends-on (:cl-ppcre :flexi-streams) :components ((:module "test" :serial t :components ((:file "packages") (:file "tests") (:file "perl-tests"))))) (defmethod perform ((o test-op) (c (eql (find-system :cl-ppcre)))) (operate 'load-op :cl-ppcre-test) (funcall (intern (symbol-name :run-all-tests) (find-package :cl-ppcre-test)))) cl-ppcre-2.0.3/closures.lisp0000644000175700010010000005262711254505512014203 0ustar ediNone;;; -*- Mode: LISP; Syntax: COMMON-LISP; Package: CL-PPCRE; Base: 10 -*- ;;; $Header: /usr/local/cvsrep/cl-ppcre/closures.lisp,v 1.45 2009/09/17 19:17:30 edi Exp $ ;;; Here we create the closures which together build the final ;;; scanner. ;;; Copyright (c) 2002-2009, Dr. Edmund Weitz. All rights reserved. ;;; Redistribution and use in source and binary forms, with or without ;;; modification, are permitted provided that the following conditions ;;; are met: ;;; * Redistributions of source code must retain the above copyright ;;; notice, this list of conditions and the following disclaimer. ;;; * Redistributions in binary form must reproduce the above ;;; copyright notice, this list of conditions and the following ;;; disclaimer in the documentation and/or other materials ;;; provided with the distribution. ;;; THIS SOFTWARE IS PROVIDED BY THE AUTHOR 'AS IS' AND ANY EXPRESSED ;;; OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED ;;; WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ;;; ARE DISCLAIMED. IN NO EVENT SHALL THE AUTHOR BE LIABLE FOR ANY ;;; DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL ;;; DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE ;;; GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS ;;; INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, ;;; WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING ;;; NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE OF THIS ;;; SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. (in-package :cl-ppcre) (declaim (inline *string*= *string*-equal)) (defun *string*= (string2 start1 end1 start2 end2) "Like STRING=, i.e. compares the special string *STRING* from START1 to END1 with STRING2 from START2 to END2. Note that there's no boundary check - this has to be implemented by the caller." (declare #.*standard-optimize-settings*) (declare (fixnum start1 end1 start2 end2)) (loop for string1-idx of-type fixnum from start1 below end1 for string2-idx of-type fixnum from start2 below end2 always (char= (schar *string* string1-idx) (schar string2 string2-idx)))) (defun *string*-equal (string2 start1 end1 start2 end2) "Like STRING-EQUAL, i.e. compares the special string *STRING* from START1 to END1 with STRING2 from START2 to END2. Note that there's no boundary check - this has to be implemented by the caller." (declare #.*standard-optimize-settings*) (declare (fixnum start1 end1 start2 end2)) (loop for string1-idx of-type fixnum from start1 below end1 for string2-idx of-type fixnum from start2 below end2 always (char-equal (schar *string* string1-idx) (schar string2 string2-idx)))) (defgeneric create-matcher-aux (regex next-fn) (declare #.*standard-optimize-settings*) (:documentation "Creates a closure which takes one parameter, START-POS, and tests whether REGEX can match *STRING* at START-POS such that the call to NEXT-FN after the match would succeed.")) (defmethod create-matcher-aux ((seq seq) next-fn) (declare #.*standard-optimize-settings*) ;; the closure for a SEQ is a chain of closures for the elements of ;; this sequence which call each other in turn; the last closure ;; calls NEXT-FN (loop for element in (reverse (elements seq)) for curr-matcher = next-fn then next-matcher for next-matcher = (create-matcher-aux element curr-matcher) finally (return next-matcher))) (defmethod create-matcher-aux ((alternation alternation) next-fn) (declare #.*standard-optimize-settings*) ;; first create closures for all alternations of ALTERNATION (let ((all-matchers (mapcar #'(lambda (choice) (create-matcher-aux choice next-fn)) (choices alternation)))) ;; now create a closure which checks if one of the closures ;; created above can succeed (lambda (start-pos) (declare (fixnum start-pos)) (loop for matcher in all-matchers thereis (funcall (the function matcher) start-pos))))) (defmethod create-matcher-aux ((register register) next-fn) (declare #.*standard-optimize-settings*) ;; the position of this REGISTER within the whole regex; we start to ;; count at 0 (let ((num (num register))) (declare (fixnum num)) ;; STORE-END-OF-REG is a thin wrapper around NEXT-FN which will ;; update the corresponding values of *REGS-START* and *REGS-END* ;; after the inner matcher has succeeded (flet ((store-end-of-reg (start-pos) (declare (fixnum start-pos) (function next-fn)) (setf (svref *reg-starts* num) (svref *regs-maybe-start* num) (svref *reg-ends* num) start-pos) (funcall next-fn start-pos))) ;; the inner matcher is a closure corresponding to the regex ;; wrapped by this REGISTER (let ((inner-matcher (create-matcher-aux (regex register) #'store-end-of-reg))) (declare (function inner-matcher)) ;; here comes the actual closure for REGISTER (lambda (start-pos) (declare (fixnum start-pos)) ;; remember the old values of *REGS-START* and friends in ;; case we cannot match (let ((old-*reg-starts* (svref *reg-starts* num)) (old-*regs-maybe-start* (svref *regs-maybe-start* num)) (old-*reg-ends* (svref *reg-ends* num))) ;; we cannot use *REGS-START* here because Perl allows ;; regular expressions like /(a|\1x)*/ (setf (svref *regs-maybe-start* num) start-pos) (let ((next-pos (funcall inner-matcher start-pos))) (unless next-pos ;; restore old values on failure (setf (svref *reg-starts* num) old-*reg-starts* (svref *regs-maybe-start* num) old-*regs-maybe-start* (svref *reg-ends* num) old-*reg-ends*)) next-pos))))))) (defmethod create-matcher-aux ((lookahead lookahead) next-fn) (declare #.*standard-optimize-settings*) ;; create a closure which just checks for the inner regex and ;; doesn't care about NEXT-FN (let ((test-matcher (create-matcher-aux (regex lookahead) #'identity))) (declare (function next-fn test-matcher)) (if (positivep lookahead) ;; positive look-ahead: check success of inner regex, then call ;; NEXT-FN (lambda (start-pos) (and (funcall test-matcher start-pos) (funcall next-fn start-pos))) ;; negative look-ahead: check failure of inner regex, then call ;; NEXT-FN (lambda (start-pos) (and (not (funcall test-matcher start-pos)) (funcall next-fn start-pos)))))) (defmethod create-matcher-aux ((lookbehind lookbehind) next-fn) (declare #.*standard-optimize-settings*) (let ((len (len lookbehind)) ;; create a closure which just checks for the inner regex and ;; doesn't care about NEXT-FN (test-matcher (create-matcher-aux (regex lookbehind) #'identity))) (declare (function next-fn test-matcher) (fixnum len)) (if (positivep lookbehind) ;; positive look-behind: check success of inner regex (if we're ;; far enough from the start of *STRING*), then call NEXT-FN (lambda (start-pos) (declare (fixnum start-pos)) (and (>= (- start-pos (or *real-start-pos* *start-pos*)) len) (funcall test-matcher (- start-pos len)) (funcall next-fn start-pos))) ;; negative look-behind: check failure of inner regex (if we're ;; far enough from the start of *STRING*), then call NEXT-FN (lambda (start-pos) (declare (fixnum start-pos)) (and (or (< (- start-pos (or *real-start-pos* *start-pos*)) len) (not (funcall test-matcher (- start-pos len)))) (funcall next-fn start-pos)))))) (defmacro insert-char-class-tester ((char-class chr-expr) &body body) "Utility macro to replace each occurence of '\(CHAR-CLASS-TEST) within BODY with the correct test (corresponding to CHAR-CLASS) against CHR-EXPR." (with-rebinding (char-class) (with-unique-names (test-function) (flet ((substitute-char-class-tester (new) (subst new '(char-class-test) body :test #'equalp))) `(let ((,test-function (test-function ,char-class))) ,@(substitute-char-class-tester `(funcall ,test-function ,chr-expr))))))) (defmethod create-matcher-aux ((char-class char-class) next-fn) (declare #.*standard-optimize-settings*) (declare (function next-fn)) ;; insert a test against the current character within *STRING* (insert-char-class-tester (char-class (schar *string* start-pos)) (lambda (start-pos) (declare (fixnum start-pos)) (and (< start-pos *end-pos*) (char-class-test) (funcall next-fn (1+ start-pos)))))) (defmethod create-matcher-aux ((str str) next-fn) (declare #.*standard-optimize-settings*) (declare (fixnum *end-string-pos*) (function next-fn) ;; this special value is set by CREATE-SCANNER when the ;; closures are built (special end-string)) (let* ((len (len str)) (case-insensitive-p (case-insensitive-p str)) (start-of-end-string-p (start-of-end-string-p str)) (skip (skip str)) (str (str str)) (chr (schar str 0)) (end-string (and end-string (str end-string))) (end-string-len (if end-string (length end-string) nil))) (declare (fixnum len)) (cond ((and start-of-end-string-p case-insensitive-p) ;; closure for the first STR which belongs to the constant ;; string at the end of the regular expression; ;; case-insensitive version (lambda (start-pos) (declare (fixnum start-pos end-string-len)) (let ((test-end-pos (+ start-pos end-string-len))) (declare (fixnum test-end-pos)) ;; either we're at *END-STRING-POS* (which means that ;; it has already been confirmed that end-string ;; starts here) or we really have to test (and (or (= start-pos *end-string-pos*) (and (<= test-end-pos *end-pos*) (*string*-equal end-string start-pos test-end-pos 0 end-string-len))) (funcall next-fn (+ start-pos len)))))) (start-of-end-string-p ;; closure for the first STR which belongs to the constant ;; string at the end of the regular expression; ;; case-sensitive version (lambda (start-pos) (declare (fixnum start-pos end-string-len)) (let ((test-end-pos (+ start-pos end-string-len))) (declare (fixnum test-end-pos)) ;; either we're at *END-STRING-POS* (which means that ;; it has already been confirmed that end-string ;; starts here) or we really have to test (and (or (= start-pos *end-string-pos*) (and (<= test-end-pos *end-pos*) (*string*= end-string start-pos test-end-pos 0 end-string-len))) (funcall next-fn (+ start-pos len)))))) (skip ;; a STR which can be skipped because some other function ;; has already confirmed that it matches (lambda (start-pos) (declare (fixnum start-pos)) (funcall next-fn (+ start-pos len)))) ((and (= len 1) case-insensitive-p) ;; STR represent exactly one character; case-insensitive ;; version (lambda (start-pos) (declare (fixnum start-pos)) (and (< start-pos *end-pos*) (char-equal (schar *string* start-pos) chr) (funcall next-fn (1+ start-pos))))) ((= len 1) ;; STR represent exactly one character; case-sensitive ;; version (lambda (start-pos) (declare (fixnum start-pos)) (and (< start-pos *end-pos*) (char= (schar *string* start-pos) chr) (funcall next-fn (1+ start-pos))))) (case-insensitive-p ;; general case, case-insensitive version (lambda (start-pos) (declare (fixnum start-pos)) (let ((next-pos (+ start-pos len))) (declare (fixnum next-pos)) (and (<= next-pos *end-pos*) (*string*-equal str start-pos next-pos 0 len) (funcall next-fn next-pos))))) (t ;; general case, case-sensitive version (lambda (start-pos) (declare (fixnum start-pos)) (let ((next-pos (+ start-pos len))) (declare (fixnum next-pos)) (and (<= next-pos *end-pos*) (*string*= str start-pos next-pos 0 len) (funcall next-fn next-pos)))))))) (declaim (inline word-boundary-p)) (defun word-boundary-p (start-pos) "Check whether START-POS is a word-boundary within *STRING*." (declare #.*standard-optimize-settings*) (declare (fixnum start-pos)) (let ((1-start-pos (1- start-pos)) (*start-pos* (or *real-start-pos* *start-pos*))) ;; either the character before START-POS is a word-constituent and ;; the character at START-POS isn't... (or (and (or (= start-pos *end-pos*) (and (< start-pos *end-pos*) (not (word-char-p (schar *string* start-pos))))) (and (< 1-start-pos *end-pos*) (<= *start-pos* 1-start-pos) (word-char-p (schar *string* 1-start-pos)))) ;; ...or vice versa (and (or (= start-pos *start-pos*) (and (< 1-start-pos *end-pos*) (<= *start-pos* 1-start-pos) (not (word-char-p (schar *string* 1-start-pos))))) (and (< start-pos *end-pos*) (word-char-p (schar *string* start-pos))))))) (defmethod create-matcher-aux ((word-boundary word-boundary) next-fn) (declare #.*standard-optimize-settings*) (declare (function next-fn)) (if (negatedp word-boundary) (lambda (start-pos) (and (not (word-boundary-p start-pos)) (funcall next-fn start-pos))) (lambda (start-pos) (and (word-boundary-p start-pos) (funcall next-fn start-pos))))) (defmethod create-matcher-aux ((everything everything) next-fn) (declare #.*standard-optimize-settings*) (declare (function next-fn)) (if (single-line-p everything) ;; closure for single-line-mode: we really match everything, so we ;; just advance the index into *STRING* by one and carry on (lambda (start-pos) (declare (fixnum start-pos)) (and (< start-pos *end-pos*) (funcall next-fn (1+ start-pos)))) ;; not single-line-mode, so we have to make sure we don't match ;; #\Newline (lambda (start-pos) (declare (fixnum start-pos)) (and (< start-pos *end-pos*) (char/= (schar *string* start-pos) #\Newline) (funcall next-fn (1+ start-pos)))))) (defmethod create-matcher-aux ((anchor anchor) next-fn) (declare #.*standard-optimize-settings*) (declare (function next-fn)) (let ((startp (startp anchor)) (multi-line-p (multi-line-p anchor))) (cond ((no-newline-p anchor) ;; this must be an end-anchor and it must be modeless, so ;; we just have to check whether START-POS equals ;; *END-POS* (lambda (start-pos) (declare (fixnum start-pos)) (and (= start-pos *end-pos*) (funcall next-fn start-pos)))) ((and startp multi-line-p) ;; a start-anchor in multi-line-mode: check if we're at ;; *START-POS* or if the last character was #\Newline (lambda (start-pos) (declare (fixnum start-pos)) (let ((*start-pos* (or *real-start-pos* *start-pos*))) (and (or (= start-pos *start-pos*) (and (<= start-pos *end-pos*) (> start-pos *start-pos*) (char= #\Newline (schar *string* (1- start-pos))))) (funcall next-fn start-pos))))) (startp ;; a start-anchor which is not in multi-line-mode, so just ;; check whether we're at *START-POS* (lambda (start-pos) (declare (fixnum start-pos)) (and (= start-pos (or *real-start-pos* *start-pos*)) (funcall next-fn start-pos)))) (multi-line-p ;; an end-anchor in multi-line-mode: check if we're at ;; *END-POS* or if the character we're looking at is ;; #\Newline (lambda (start-pos) (declare (fixnum start-pos)) (and (or (= start-pos *end-pos*) (and (< start-pos *end-pos*) (char= #\Newline (schar *string* start-pos)))) (funcall next-fn start-pos)))) (t ;; an end-anchor which is not in multi-line-mode, so just ;; check if we're at *END-POS* or if we're looking at ;; #\Newline and there's nothing behind it (lambda (start-pos) (declare (fixnum start-pos)) (and (or (= start-pos *end-pos*) (and (= start-pos (1- *end-pos*)) (char= #\Newline (schar *string* start-pos)))) (funcall next-fn start-pos))))))) (defmethod create-matcher-aux ((back-reference back-reference) next-fn) (declare #.*standard-optimize-settings*) (declare (function next-fn)) ;; the position of the corresponding REGISTER within the whole ;; regex; we start to count at 0 (let ((num (num back-reference))) (if (case-insensitive-p back-reference) ;; the case-insensitive version (lambda (start-pos) (declare (fixnum start-pos)) (let ((reg-start (svref *reg-starts* num)) (reg-end (svref *reg-ends* num))) ;; only bother to check if the corresponding REGISTER as ;; matched successfully already (and reg-start (let ((next-pos (+ start-pos (- (the fixnum reg-end) (the fixnum reg-start))))) (declare (fixnum next-pos)) (and (<= next-pos *end-pos*) (*string*-equal *string* start-pos next-pos reg-start reg-end) (funcall next-fn next-pos)))))) ;; the case-sensitive version (lambda (start-pos) (declare (fixnum start-pos)) (let ((reg-start (svref *reg-starts* num)) (reg-end (svref *reg-ends* num))) ;; only bother to check if the corresponding REGISTER as ;; matched successfully already (and reg-start (let ((next-pos (+ start-pos (- (the fixnum reg-end) (the fixnum reg-start))))) (declare (fixnum next-pos)) (and (<= next-pos *end-pos*) (*string*= *string* start-pos next-pos reg-start reg-end) (funcall next-fn next-pos))))))))) (defmethod create-matcher-aux ((branch branch) next-fn) (declare #.*standard-optimize-settings*) (let* ((test (test branch)) (then-matcher (create-matcher-aux (then-regex branch) next-fn)) (else-matcher (create-matcher-aux (else-regex branch) next-fn))) (declare (function then-matcher else-matcher)) (cond ((numberp test) (lambda (start-pos) (declare (fixnum test)) (if (and (< test (length *reg-starts*)) (svref *reg-starts* test)) (funcall then-matcher start-pos) (funcall else-matcher start-pos)))) (t (let ((test-matcher (create-matcher-aux test #'identity))) (declare (function test-matcher)) (lambda (start-pos) (if (funcall test-matcher start-pos) (funcall then-matcher start-pos) (funcall else-matcher start-pos)))))))) (defmethod create-matcher-aux ((standalone standalone) next-fn) (declare #.*standard-optimize-settings*) (let ((inner-matcher (create-matcher-aux (regex standalone) #'identity))) (declare (function next-fn inner-matcher)) (lambda (start-pos) (let ((next-pos (funcall inner-matcher start-pos))) (and next-pos (funcall next-fn next-pos)))))) (defmethod create-matcher-aux ((filter filter) next-fn) (declare #.*standard-optimize-settings*) (let ((fn (fn filter))) (lambda (start-pos) (let ((next-pos (funcall fn start-pos))) (and next-pos (funcall next-fn next-pos)))))) (defmethod create-matcher-aux ((void void) next-fn) (declare #.*standard-optimize-settings*) ;; optimize away VOIDs: don't create a closure, just return NEXT-FN next-fn) cl-ppcre-2.0.3/convert.lisp0000644000175700010010000011732111254505513014016 0ustar ediNone;;; -*- Mode: LISP; Syntax: COMMON-LISP; Package: CL-PPCRE; Base: 10 -*- ;;; $Header: /usr/local/cvsrep/cl-ppcre/convert.lisp,v 1.57 2009/09/17 19:17:31 edi Exp $ ;;; Here the parse tree is converted into its internal representation ;;; using REGEX objects. At the same time some optimizations are ;;; already applied. ;;; Copyright (c) 2002-2009, Dr. Edmund Weitz. All rights reserved. ;;; Redistribution and use in source and binary forms, with or without ;;; modification, are permitted provided that the following conditions ;;; are met: ;;; * Redistributions of source code must retain the above copyright ;;; notice, this list of conditions and the following disclaimer. ;;; * Redistributions in binary form must reproduce the above ;;; copyright notice, this list of conditions and the following ;;; disclaimer in the documentation and/or other materials ;;; provided with the distribution. ;;; THIS SOFTWARE IS PROVIDED BY THE AUTHOR 'AS IS' AND ANY EXPRESSED ;;; OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED ;;; WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ;;; ARE DISCLAIMED. IN NO EVENT SHALL THE AUTHOR BE LIABLE FOR ANY ;;; DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL ;;; DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE ;;; GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS ;;; INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, ;;; WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING ;;; NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE OF THIS ;;; SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. (in-package :cl-ppcre) ;;; The flags that represent the "ism" modifiers are always kept ;;; together in a three-element list. We use the following macros to ;;; access individual elements. (defmacro case-insensitive-mode-p (flags) "Accessor macro to extract the first flag out of a three-element flag list." `(first ,flags)) (defmacro multi-line-mode-p (flags) "Accessor macro to extract the second flag out of a three-element flag list." `(second ,flags)) (defmacro single-line-mode-p (flags) "Accessor macro to extract the third flag out of a three-element flag list." `(third ,flags)) (defun set-flag (token) "Reads a flag token and sets or unsets the corresponding entry in the special FLAGS list." (declare #.*standard-optimize-settings*) (declare (special flags)) (case token ((:case-insensitive-p) (setf (case-insensitive-mode-p flags) t)) ((:case-sensitive-p) (setf (case-insensitive-mode-p flags) nil)) ((:multi-line-mode-p) (setf (multi-line-mode-p flags) t)) ((:not-multi-line-mode-p) (setf (multi-line-mode-p flags) nil)) ((:single-line-mode-p) (setf (single-line-mode-p flags) t)) ((:not-single-line-mode-p) (setf (single-line-mode-p flags) nil)) (otherwise (signal-syntax-error "Unknown flag token ~A." token)))) (defgeneric resolve-property (property) (:documentation "Resolves PROPERTY to a unary character test function. PROPERTY can either be a function designator or it can be a string which is resolved using *PROPERTY-RESOLVER*.") (:method ((property-name string)) (funcall *property-resolver* property-name)) (:method ((function-name symbol)) function-name) (:method ((test-function function)) test-function)) (defun convert-char-class-to-test-function (list invertedp case-insensitive-p) "Combines all items in LIST into test function and returns a logical-OR combination of these functions. Items can be single characters, character ranges like \(:RANGE #\\A #\\E), or special character classes like :DIGIT-CLASS. Does the right thing with respect to case-\(in)sensitivity as specified by the special variable FLAGS." (declare #.*standard-optimize-settings*) (declare (special flags)) (let ((test-functions (loop for item in list collect (cond ((characterp item) ;; rebind so closure captures the right one (let ((this-char item)) (lambda (char) (declare (character char this-char)) (char= char this-char)))) ((symbolp item) (case item ((:digit-class) #'digit-char-p) ((:non-digit-class) (complement* #'digit-char-p)) ((:whitespace-char-class) #'whitespacep) ((:non-whitespace-char-class) (complement* #'whitespacep)) ((:word-char-class) #'word-char-p) ((:non-word-char-class) (complement* #'word-char-p)) (otherwise (signal-syntax-error "Unknown symbol ~A in character class." item)))) ((and (consp item) (eq (first item) :property)) (resolve-property (second item))) ((and (consp item) (eq (first item) :inverted-property)) (complement* (resolve-property (second item)))) ((and (consp item) (eq (first item) :range)) (let ((from (second item)) (to (third item))) (when (char> from to) (signal-syntax-error "Invalid range from ~S to ~S in char-class." from to)) (lambda (char) (declare (character char from to)) (char<= from char to)))) (t (signal-syntax-error "Unknown item ~A in char-class list." item)))))) (unless test-functions (signal-syntax-error "Empty character class.")) (cond ((cdr test-functions) (cond ((and invertedp case-insensitive-p) (lambda (char) (declare (character char)) (loop with both-case-p = (both-case-p char) with char-down = (if both-case-p (char-downcase char) char) with char-up = (if both-case-p (char-upcase char) nil) for test-function in test-functions never (or (funcall test-function char-down) (and char-up (funcall test-function char-up)))))) (case-insensitive-p (lambda (char) (declare (character char)) (loop with both-case-p = (both-case-p char) with char-down = (if both-case-p (char-downcase char) char) with char-up = (if both-case-p (char-upcase char) nil) for test-function in test-functions thereis (or (funcall test-function char-down) (and char-up (funcall test-function char-up)))))) (invertedp (lambda (char) (loop for test-function in test-functions never (funcall test-function char)))) (t (lambda (char) (loop for test-function in test-functions thereis (funcall test-function char)))))) ;; there's only one test-function (t (let ((test-function (first test-functions))) (cond ((and invertedp case-insensitive-p) (lambda (char) (declare (character char)) (not (or (funcall test-function (char-downcase char)) (and (both-case-p char) (funcall test-function (char-upcase char))))))) (case-insensitive-p (lambda (char) (declare (character char)) (or (funcall test-function (char-downcase char)) (and (both-case-p char) (funcall test-function (char-upcase char)))))) (invertedp (complement* test-function)) (t test-function))))))) (defun maybe-split-repetition (regex greedyp minimum maximum min-len length reg-seen) "Splits a REPETITION object into a constant and a varying part if applicable, i.e. something like a{3,} -> a{3}a* The arguments to this function correspond to the REPETITION slots of the same name." (declare #.*standard-optimize-settings*) (declare (fixnum minimum) (type (or fixnum null) maximum)) ;; note the usage of COPY-REGEX here; we can't use the same REGEX ;; object in both REPETITIONS because they will have different ;; offsets (when maximum (when (zerop maximum) ;; trivial case: don't repeat at all (return-from maybe-split-repetition (make-instance 'void))) (when (= 1 minimum maximum) ;; another trivial case: "repeat" exactly once (return-from maybe-split-repetition regex))) ;; first set up the constant part of the repetition ;; maybe that's all we need (let ((constant-repetition (if (plusp minimum) (make-instance 'repetition :regex (copy-regex regex) :greedyp greedyp :minimum minimum :maximum minimum :min-len min-len :len length :contains-register-p reg-seen) ;; don't create garbage if minimum is 0 nil))) (when (and maximum (= maximum minimum)) (return-from maybe-split-repetition ;; no varying part needed because min = max constant-repetition)) ;; now construct the varying part (let ((varying-repetition (make-instance 'repetition :regex regex :greedyp greedyp :minimum 0 :maximum (if maximum (- maximum minimum) nil) :min-len min-len :len length :contains-register-p reg-seen))) (cond ((zerop minimum) ;; min = 0, no constant part needed varying-repetition) ((= 1 minimum) ;; min = 1, constant part needs no REPETITION wrapped around (make-instance 'seq :elements (list (copy-regex regex) varying-repetition))) (t ;; general case (make-instance 'seq :elements (list constant-repetition varying-repetition))))))) ;; During the conversion of the parse tree we keep track of the start ;; of the parse tree in the special variable STARTS-WITH which'll ;; either hold a STR object or an EVERYTHING object. The latter is the ;; case if the regex starts with ".*" which implicitly anchors the ;; regex at the start (perhaps modulo #\Newline). (defun maybe-accumulate (str) "Accumulate STR into the special variable STARTS-WITH if ACCUMULATE-START-P (also special) is true and STARTS-WITH is either NIL or a STR object of the same case mode. Always returns NIL." (declare #.*standard-optimize-settings*) (declare (special accumulate-start-p starts-with)) (declare (ftype (function (t) fixnum) len)) (when accumulate-start-p (etypecase starts-with (str ;; STARTS-WITH already holds a STR, so we check if we can ;; concatenate (cond ((eq (case-insensitive-p starts-with) (case-insensitive-p str)) ;; we modify STARTS-WITH in place (setf (len starts-with) (+ (len starts-with) (len str))) ;; note that we use SLOT-VALUE because the accessor ;; STR has a declared FTYPE which doesn't fit here (adjust-array (slot-value starts-with 'str) (len starts-with) :fill-pointer t) (setf (subseq (slot-value starts-with 'str) (- (len starts-with) (len str))) (str str) ;; STR objects that are parts of STARTS-WITH ;; always have their SKIP slot set to true ;; because the SCAN function will take care of ;; them, i.e. the matcher can ignore them (skip str) t)) (t (setq accumulate-start-p nil)))) (null ;; STARTS-WITH is still empty, so we create a new STR object (setf starts-with (make-instance 'str :str "" :case-insensitive-p (case-insensitive-p str)) ;; INITIALIZE-INSTANCE will coerce the STR to a simple ;; string, so we have to fill it afterwards (slot-value starts-with 'str) (make-array (len str) :initial-contents (str str) :element-type 'character :fill-pointer t :adjustable t) (len starts-with) (len str) ;; see remark about SKIP above (skip str) t)) (everything ;; STARTS-WITH already holds an EVERYTHING object - we can't ;; concatenate (setq accumulate-start-p nil)))) nil) (declaim (inline convert-aux)) (defun convert-aux (parse-tree) "Converts the parse tree PARSE-TREE into a REGEX object and returns it. Will also - split and optimize repetitions, - accumulate strings or EVERYTHING objects into the special variable STARTS-WITH, - keep track of all registers seen in the special variable REG-NUM, - keep track of all named registers seen in the special variable REG-NAMES - keep track of the highest backreference seen in the special variable MAX-BACK-REF, - maintain and adher to the currently applicable modifiers in the special variable FLAGS, and - maybe even wash your car..." (declare #.*standard-optimize-settings*) (if (consp parse-tree) (convert-compound-parse-tree (first parse-tree) parse-tree) (convert-simple-parse-tree parse-tree))) (defgeneric convert-compound-parse-tree (token parse-tree &key) (declare #.*standard-optimize-settings*) (:documentation "Helper function for CONVERT-AUX which converts parse trees which are conses and dispatches on TOKEN which is the first element of the parse tree.") (:method ((token t) parse-tree &key) (signal-syntax-error "Unknown token ~A in parse-tree." token))) (defmethod convert-compound-parse-tree ((token (eql :sequence)) parse-tree &key) "The case for parse trees like \(:SEQUENCE {}*)." (declare #.*standard-optimize-settings*) (cond ((cddr parse-tree) ;; this is essentially like ;; (MAPCAR 'CONVERT-AUX (REST PARSE-TREE)) ;; but we don't cons a new list (loop for parse-tree-rest on (rest parse-tree) while parse-tree-rest do (setf (car parse-tree-rest) (convert-aux (car parse-tree-rest)))) (make-instance 'seq :elements (rest parse-tree))) (t (convert-aux (second parse-tree))))) (defmethod convert-compound-parse-tree ((token (eql :group)) parse-tree &key) "The case for parse trees like \(:GROUP {}*). This is a syntactical construct equivalent to :SEQUENCE intended to keep the effect of modifiers local." (declare #.*standard-optimize-settings*) (declare (special flags)) ;; make a local copy of FLAGS and shadow the global value while we ;; descend into the enclosed regexes (let ((flags (copy-list flags))) (declare (special flags)) (cond ((cddr parse-tree) (loop for parse-tree-rest on (rest parse-tree) while parse-tree-rest do (setf (car parse-tree-rest) (convert-aux (car parse-tree-rest)))) (make-instance 'seq :elements (rest parse-tree))) (t (convert-aux (second parse-tree)))))) (defmethod convert-compound-parse-tree ((token (eql :alternation)) parse-tree &key) "The case for \(:ALTERNATION {}*)." (declare #.*standard-optimize-settings*) (declare (special accumulate-start-p)) ;; we must stop accumulating objects into STARTS-WITH once we reach ;; an alternation (setq accumulate-start-p nil) (loop for parse-tree-rest on (rest parse-tree) while parse-tree-rest do (setf (car parse-tree-rest) (convert-aux (car parse-tree-rest)))) (make-instance 'alternation :choices (rest parse-tree))) (defmethod convert-compound-parse-tree ((token (eql :branch)) parse-tree &key) "The case for \(:BRANCH ). Here, must be look-ahead, look-behind or number; if is an alternation it must have one or two choices." (declare #.*standard-optimize-settings*) (declare (special accumulate-start-p)) (setq accumulate-start-p nil) (let* ((test-candidate (second parse-tree)) (test (cond ((numberp test-candidate) (when (zerop (the fixnum test-candidate)) (signal-syntax-error "Register 0 doesn't exist: ~S." parse-tree)) (1- (the fixnum test-candidate))) (t (convert-aux test-candidate)))) (alternations (convert-aux (third parse-tree)))) (when (and (not (numberp test)) (not (typep test 'lookahead)) (not (typep test 'lookbehind))) (signal-syntax-error "Branch test must be look-ahead, look-behind or number: ~S." parse-tree)) (typecase alternations (alternation (case (length (choices alternations)) ((0) (signal-syntax-error "No choices in branch: ~S." parse-tree)) ((1) (make-instance 'branch :test test :then-regex (first (choices alternations)))) ((2) (make-instance 'branch :test test :then-regex (first (choices alternations)) :else-regex (second (choices alternations)))) (otherwise (signal-syntax-error "Too much choices in branch: ~S." parse-tree)))) (t (make-instance 'branch :test test :then-regex alternations))))) (defmethod convert-compound-parse-tree ((token (eql :positive-lookahead)) parse-tree &key) "The case for \(:POSITIVE-LOOKAHEAD )." (declare #.*standard-optimize-settings*) (declare (special flags accumulate-start-p)) ;; keep the effect of modifiers local to the enclosed regex and stop ;; accumulating into STARTS-WITH (setq accumulate-start-p nil) (let ((flags (copy-list flags))) (declare (special flags)) (make-instance 'lookahead :regex (convert-aux (second parse-tree)) :positivep t))) (defmethod convert-compound-parse-tree ((token (eql :negative-lookahead)) parse-tree &key) "The case for \(:NEGATIVE-LOOKAHEAD )." (declare #.*standard-optimize-settings*) ;; do the same as for positive look-aheads and just switch afterwards (let ((regex (convert-compound-parse-tree :positive-lookahead parse-tree))) (setf (slot-value regex 'positivep) nil) regex)) (defmethod convert-compound-parse-tree ((token (eql :positive-lookbehind)) parse-tree &key) "The case for \(:POSITIVE-LOOKBEHIND )." (declare #.*standard-optimize-settings*) (declare (special flags accumulate-start-p)) ;; keep the effect of modifiers local to the enclosed regex and stop ;; accumulating into STARTS-WITH (setq accumulate-start-p nil) (let* ((flags (copy-list flags)) (regex (convert-aux (second parse-tree))) (len (regex-length regex))) (declare (special flags)) ;; lookbehind assertions must be of fixed length (unless len (signal-syntax-error "Variable length look-behind not implemented \(yet): ~S." parse-tree)) (make-instance 'lookbehind :regex regex :positivep t :len len))) (defmethod convert-compound-parse-tree ((token (eql :negative-lookbehind)) parse-tree &key) "The case for \(:NEGATIVE-LOOKBEHIND )." (declare #.*standard-optimize-settings*) ;; do the same as for positive look-behinds and just switch afterwards (let ((regex (convert-compound-parse-tree :positive-lookbehind parse-tree))) (setf (slot-value regex 'positivep) nil) regex)) (defmethod convert-compound-parse-tree ((token (eql :greedy-repetition)) parse-tree &key (greedyp t)) "The case for \(:GREEDY-REPETITION|:NON-GREEDY-REPETITION ). This function is also used for the non-greedy case in which case it is called with GREEDYP set to NIL as you would expect." (declare #.*standard-optimize-settings*) (declare (special accumulate-start-p starts-with)) ;; remember the value of ACCUMULATE-START-P upon entering (let ((local-accumulate-start-p accumulate-start-p)) (let ((minimum (second parse-tree)) (maximum (third parse-tree))) (declare (fixnum minimum)) (declare (type (or null fixnum) maximum)) (unless (and maximum (= 1 minimum maximum)) ;; set ACCUMULATE-START-P to NIL for the rest of ;; the conversion because we can't continue to ;; accumulate inside as well as after a proper ;; repetition (setq accumulate-start-p nil)) (let* (reg-seen (regex (convert-aux (fourth parse-tree))) (min-len (regex-min-length regex)) (length (regex-length regex))) ;; note that this declaration already applies to ;; the call to CONVERT-AUX above (declare (special reg-seen)) (when (and local-accumulate-start-p (not starts-with) (zerop minimum) (not maximum)) ;; if this repetition is (equivalent to) ".*" ;; and if we're at the start of the regex we ;; remember it for ADVANCE-FN (see the SCAN ;; function) (setq starts-with (everythingp regex))) (if (or (not reg-seen) (not greedyp) (not length) (zerop length) (and maximum (= minimum maximum))) ;; the repetition doesn't enclose a register, or ;; it's not greedy, or we can't determine it's ;; (inner) length, or the length is zero, or the ;; number of repetitions is fixed; in all of ;; these cases we don't bother to optimize (maybe-split-repetition regex greedyp minimum maximum min-len length reg-seen) ;; otherwise we make a transformation that looks ;; roughly like one of ;; * -> (?:*)? ;; + -> * ;; where the trick is that as much as possible ;; registers from are removed in ;; (let* (reg-seen ; new instance for REMOVE-REGISTERS (remove-registers-p t) (inner-regex (remove-registers regex)) (inner-repetition ;; this is the "" part (maybe-split-repetition inner-regex ;; always greedy t ;; reduce minimum by 1 ;; unless it's already 0 (if (zerop minimum) 0 (1- minimum)) ;; reduce maximum by 1 ;; unless it's NIL (and maximum (1- maximum)) min-len length reg-seen)) (inner-seq ;; this is the "*" part (make-instance 'seq :elements (list inner-repetition regex)))) ;; note that this declaration already applies ;; to the call to REMOVE-REGISTERS above (declare (special remove-registers-p reg-seen)) ;; wrap INNER-SEQ with a greedy ;; {0,1}-repetition (i.e. "?") if necessary (if (plusp minimum) inner-seq (maybe-split-repetition inner-seq t 0 1 min-len nil t)))))))) (defmethod convert-compound-parse-tree ((token (eql :non-greedy-repetition)) parse-tree &key) "The case for \(:NON-GREEDY-REPETITION )." (declare #.*standard-optimize-settings*) ;; just dispatch to the method above with GREEDYP explicitly set to NIL (convert-compound-parse-tree :greedy-repetition parse-tree :greedyp nil)) (defmethod convert-compound-parse-tree ((token (eql :register)) parse-tree &key name) "The case for \(:REGISTER ). Also used for named registers when NAME is not NIL." (declare #.*standard-optimize-settings*) (declare (special flags reg-num reg-names)) ;; keep the effect of modifiers local to the enclosed regex; also, ;; assign the current value of REG-NUM to the corresponding slot of ;; the REGISTER object and increase this counter afterwards; for ;; named register update REG-NAMES and set the corresponding name ;; slot of the REGISTER object too (let ((flags (copy-list flags)) (stored-reg-num reg-num)) (declare (special flags reg-seen named-reg-seen)) (setq reg-seen t) (when name (setq named-reg-seen t)) (incf (the fixnum reg-num)) (push name reg-names) (make-instance 'register :regex (convert-aux (if name (third parse-tree) (second parse-tree))) :num stored-reg-num :name name))) (defmethod convert-compound-parse-tree ((token (eql :named-register)) parse-tree &key) "The case for \(:NAMED-REGISTER )." (declare #.*standard-optimize-settings*) ;; call the method above and use the :NAME keyword argument (convert-compound-parse-tree :register parse-tree :name (copy-seq (second parse-tree)))) (defmethod convert-compound-parse-tree ((token (eql :filter)) parse-tree &key) "The case for \(:FILTER &optional )." (declare #.*standard-optimize-settings*) (declare (special accumulate-start-p)) ;; stop accumulating into STARTS-WITH (setq accumulate-start-p nil) (make-instance 'filter :fn (second parse-tree) :len (third parse-tree))) (defmethod convert-compound-parse-tree ((token (eql :standalone)) parse-tree &key) "The case for \(:STANDALONE )." (declare #.*standard-optimize-settings*) (declare (special flags accumulate-start-p)) ;; stop accumulating into STARTS-WITH (setq accumulate-start-p nil) ;; keep the effect of modifiers local to the enclosed regex (let ((flags (copy-list flags))) (declare (special flags)) (make-instance 'standalone :regex (convert-aux (second parse-tree))))) (defmethod convert-compound-parse-tree ((token (eql :back-reference)) parse-tree &key) "The case for \(:BACK-REFERENCE |)." (declare #.*standard-optimize-settings*) (declare (special flags accumulate-start-p reg-num reg-names max-back-ref)) (let* ((backref-name (and (stringp (second parse-tree)) (second parse-tree))) (referred-regs (when backref-name ;; find which register corresponds to the given name ;; we have to deal with case where several registers share ;; the same name and collect their respective numbers (loop for name in reg-names for reg-index from 0 when (string= name backref-name) ;; NOTE: REG-NAMES stores register names in reversed ;; order REG-NUM contains number of (any) registers ;; seen so far; 1- will be done later collect (- reg-num reg-index)))) ;; store the register number for the simple case (backref-number (or (first referred-regs) (second parse-tree)))) (declare (type (or fixnum null) backref-number)) (when (or (not (typep backref-number 'fixnum)) (<= backref-number 0)) (signal-syntax-error "Illegal back-reference: ~S." parse-tree)) ;; stop accumulating into STARTS-WITH and increase MAX-BACK-REF if ;; necessary (setq accumulate-start-p nil max-back-ref (max (the fixnum max-back-ref) backref-number)) (flet ((make-back-ref (backref-number) (make-instance 'back-reference ;; we start counting from 0 internally :num (1- backref-number) :case-insensitive-p (case-insensitive-mode-p flags) ;; backref-name is NIL or string, safe to copy :name (copy-seq backref-name)))) (cond ((cdr referred-regs) ;; several registers share the same name we will try to match ;; any of them, starting with the most recent first ;; alternation is used to accomplish matching (make-instance 'alternation :choices (loop for reg-index in referred-regs collect (make-back-ref reg-index)))) ;; simple case - backref corresponds to only one register (t (make-back-ref backref-number)))))) (defmethod convert-compound-parse-tree ((token (eql :regex)) parse-tree &key) "The case for \(:REGEX )." (declare #.*standard-optimize-settings*) (convert-aux (parse-string (second parse-tree)))) (defmethod convert-compound-parse-tree ((token (eql :char-class)) parse-tree &key invertedp) "The case for \(:CHAR-CLASS {}*) where item is one of - a character, - a character range: \(:RANGE ), or - a special char class symbol like :DIGIT-CHAR-CLASS. Also used for inverted char classes when INVERTEDP is true." (declare #.*standard-optimize-settings*) (declare (special flags accumulate-start-p)) (let ((test-function (create-optimized-test-function (convert-char-class-to-test-function (rest parse-tree) invertedp (case-insensitive-mode-p flags))))) (setq accumulate-start-p nil) (make-instance 'char-class :test-function test-function))) (defmethod convert-compound-parse-tree ((token (eql :inverted-char-class)) parse-tree &key) "The case for \(:INVERTED-CHAR-CLASS {}*)." (declare #.*standard-optimize-settings*) ;; just dispatch to the "real" method (convert-compound-parse-tree :char-class parse-tree :invertedp t)) (defmethod convert-compound-parse-tree ((token (eql :property)) parse-tree &key) "The case for \(:PROPERTY ) where is a string." (declare #.*standard-optimize-settings*) (make-instance 'char-class :test-function (resolve-property (second parse-tree)))) (defmethod convert-compound-parse-tree ((token (eql :inverted-property)) parse-tree &key) "The case for \(:INVERTED-PROPERTY ) where is a string." (declare #.*standard-optimize-settings*) (make-instance 'char-class :test-function (complement* (resolve-property (second parse-tree))))) (defmethod convert-compound-parse-tree ((token (eql :flags)) parse-tree &key) "The case for \(:FLAGS {}*) where flag is a modifier symbol like :CASE-INSENSITIVE-P." (declare #.*standard-optimize-settings*) ;; set/unset the flags corresponding to the symbols ;; following :FLAGS (mapc #'set-flag (rest parse-tree)) ;; we're only interested in the side effect of ;; setting/unsetting the flags and turn this syntactical ;; construct into a VOID object which'll be optimized ;; away when creating the matcher (make-instance 'void)) (defgeneric convert-simple-parse-tree (parse-tree) (declare #.*standard-optimize-settings*) (:documentation "Helper function for CONVERT-AUX which converts parse trees which are atoms.") (:method ((parse-tree (eql :void))) (declare #.*standard-optimize-settings*) (make-instance 'void)) (:method ((parse-tree (eql :word-boundary))) (declare #.*standard-optimize-settings*) (make-instance 'word-boundary :negatedp nil)) (:method ((parse-tree (eql :non-word-boundary))) (declare #.*standard-optimize-settings*) (make-instance 'word-boundary :negatedp t)) (:method ((parse-tree (eql :everything))) (declare #.*standard-optimize-settings*) (declare (special flags accumulate-start-p)) (setq accumulate-start-p nil) (make-instance 'everything :single-line-p (single-line-mode-p flags))) (:method ((parse-tree (eql :digit-class))) (declare #.*standard-optimize-settings*) (declare (special accumulate-start-p)) (setq accumulate-start-p nil) (make-instance 'char-class :test-function #'digit-char-p)) (:method ((parse-tree (eql :word-char-class))) (declare #.*standard-optimize-settings*) (declare (special accumulate-start-p)) (setq accumulate-start-p nil) (make-instance 'char-class :test-function #'word-char-p)) (:method ((parse-tree (eql :whitespace-char-class))) (declare #.*standard-optimize-settings*) (declare (special accumulate-start-p)) (setq accumulate-start-p nil) (make-instance 'char-class :test-function #'whitespacep)) (:method ((parse-tree (eql :non-digit-class))) (declare #.*standard-optimize-settings*) (declare (special accumulate-start-p)) (setq accumulate-start-p nil) (make-instance 'char-class :test-function (complement* #'digit-char-p))) (:method ((parse-tree (eql :non-word-char-class))) (declare #.*standard-optimize-settings*) (declare (special accumulate-start-p)) (setq accumulate-start-p nil) (make-instance 'char-class :test-function (complement* #'word-char-p))) (:method ((parse-tree (eql :non-whitespace-char-class))) (declare #.*standard-optimize-settings*) (declare (special accumulate-start-p)) (setq accumulate-start-p nil) (make-instance 'char-class :test-function (complement* #'whitespacep))) (:method ((parse-tree (eql :start-anchor))) ;; Perl's "^" (declare #.*standard-optimize-settings*) (declare (special flags)) (make-instance 'anchor :startp t :multi-line-p (multi-line-mode-p flags))) (:method ((parse-tree (eql :end-anchor))) ;; Perl's "$" (declare #.*standard-optimize-settings*) (declare (special flags)) (make-instance 'anchor :startp nil :multi-line-p (multi-line-mode-p flags))) (:method ((parse-tree (eql :modeless-start-anchor))) ;; Perl's "\A" (declare #.*standard-optimize-settings*) (make-instance 'anchor :startp t)) (:method ((parse-tree (eql :modeless-end-anchor))) ;; Perl's "$\Z" (declare #.*standard-optimize-settings*) (make-instance 'anchor :startp nil)) (:method ((parse-tree (eql :modeless-end-anchor-no-newline))) ;; Perl's "$\z" (declare #.*standard-optimize-settings*) (make-instance 'anchor :startp nil :no-newline-p t)) (:method ((parse-tree (eql :case-insensitive-p))) (declare #.*standard-optimize-settings*) (set-flag parse-tree) (make-instance 'void)) (:method ((parse-tree (eql :case-sensitive-p))) (declare #.*standard-optimize-settings*) (set-flag parse-tree) (make-instance 'void)) (:method ((parse-tree (eql :multi-line-mode-p))) (declare #.*standard-optimize-settings*) (set-flag parse-tree) (make-instance 'void)) (:method ((parse-tree (eql :not-multi-line-mode-p))) (declare #.*standard-optimize-settings*) (set-flag parse-tree) (make-instance 'void)) (:method ((parse-tree (eql :single-line-mode-p))) (declare #.*standard-optimize-settings*) (set-flag parse-tree) (make-instance 'void)) (:method ((parse-tree (eql :not-single-line-mode-p))) (declare #.*standard-optimize-settings*) (set-flag parse-tree) (make-instance 'void))) (defmethod convert-simple-parse-tree ((parse-tree string)) (declare #.*standard-optimize-settings*) (declare (special flags)) ;; turn strings into STR objects and try to accumulate into ;; STARTS-WITH (let ((str (make-instance 'str :str parse-tree :case-insensitive-p (case-insensitive-mode-p flags)))) (maybe-accumulate str) str)) (defmethod convert-simple-parse-tree ((parse-tree character)) (declare #.*standard-optimize-settings*) ;; dispatch to the method for strings (convert-simple-parse-tree (string parse-tree))) (defmethod convert-simple-parse-tree (parse-tree) "The default method - check if there's a translation." (declare #.*standard-optimize-settings*) (let ((translation (and (symbolp parse-tree) (parse-tree-synonym parse-tree)))) (if translation (convert-aux (copy-tree translation)) (signal-syntax-error "Unknown token ~A in parse tree." parse-tree)))) (defun convert (parse-tree) "Converts the parse tree PARSE-TREE into an equivalent REGEX object and returns three values: the REGEX object, the number of registers seen and an object the regex starts with which is either a STR object or an EVERYTHING object \(if the regex starts with something like \".*\") or NIL." (declare #.*standard-optimize-settings*) ;; this function basically just initializes the special variables ;; and then calls CONVERT-AUX to do all the work (let* ((flags (list nil nil nil)) (reg-num 0) reg-names named-reg-seen (accumulate-start-p t) starts-with (max-back-ref 0) (converted-parse-tree (convert-aux parse-tree))) (declare (special flags reg-num reg-names named-reg-seen accumulate-start-p starts-with max-back-ref)) ;; make sure we don't reference registers which aren't there (when (> (the fixnum max-back-ref) (the fixnum reg-num)) (signal-syntax-error "Backreference to register ~A which has not been defined." max-back-ref)) (when (typep starts-with 'str) (setf (slot-value starts-with 'str) (coerce (slot-value starts-with 'str) #+:lispworks 'lw:simple-text-string #-:lispworks 'simple-string))) (values converted-parse-tree reg-num starts-with ;; we can't simply use *ALLOW-NAMED-REGISTERS* ;; since parse-tree syntax ignores it (when named-reg-seen (nreverse reg-names))))) cl-ppcre-2.0.3/doc/0000755000175700010010000000000011271772245012214 5ustar ediNonecl-ppcre-2.0.3/doc/index.html0000644000175700010010000027351211271772177014227 0ustar ediNone CL-PPCRE - Portable Perl-compatible regular expressions for Common Lisp

CL-PPCRE - Portable Perl-compatible regular expressions for Common Lisp


 

Abstract

CL-PPCRE is a portable regular expression library for Common Lisp which has the following features:
  • It is compatible with Perl.
  • It is pretty fast.
  • It is portable between ANSI-compliant Common Lisp implementations.
  • It is thread-safe.
  • In addition to specifying regular expressions as strings like in Perl you can also use S-expressions.
  • It comes with a BSD-style license so you can basically do with it whatever you want.
CL-PPCRE has been used successfully in various applications like BioBike, clutu, LoGS, CafeSpot, Eboy, or The Regex Coach.

Download shortcut: http://weitz.de/files/cl-ppcre.tar.gz.


 

Contents

  1. Download and installation
  2. Support and mailing lists
  3. The CL-PPCRE dictionary
    1. Scanning
      1. create-scanner (for Perl regex strings)
      2. create-scanner (for parse trees)
      3. scan
      4. scan-to-strings
      5. register-groups-bind
      6. do-scans
      7. do-matches
      8. do-matches-as-strings
      9. do-register-groups
      10. all-matches
      11. all-matches-as-strings
    2. Splitting and replacing
      1. split
      2. regex-replace
      3. regex-replace-all
    3. Modifying scanner behaviour
      1. *property-resolver*
      2. parse-tree-synonym
      3. define-parse-tree-synonym
      4. *regex-char-code-limit*
      5. *use-bmh-matchers*
      6. *optimize-char-classes*
      7. *allow-quoting*
      8. *allow-named-registers*
    4. Miscellaneous
      1. parse-string
      2. create-optimized-test-function
      3. quote-meta-chars
      4. regex-apropos
      5. regex-apropos-list
    5. Conditions
      1. ppcre-error
      2. ppcre-invocation-error
      3. ppcre-syntax-error
      4. ppcre-syntax-error-string
      5. ppcre-syntax-error-pos
  4. Unicode properties
    1. unicode-property-resolver
  5. Filters
  6. Compatibility with Perl
    1. Empty strings instead of undef in $1, $2, etc.
    2. Strange scoping of embedded modifiers
    3. Inconsistent capturing of $1, $2, etc.
    4. Captured groups not available outside of look-aheads and look-behinds
    5. Alternations don't always work from left to right
    6. Different names for Unicode properties
    7. "\r" doesn't work with MCL
    8. What about "\w"?
  7. Bugs and problems
    1. "\Q" doesn't work, or does it?
    2. Backslashes may confuse you...
  8. AllegroCL compatibility mode
  9. Hints, comments, performance considerations
  10. Acknowledgements

 

Download and installation

CL-PPCRE together with this documentation can be downloaded from http://weitz.de/files/cl-ppcre.tar.gz. The current version is 2.0.3.

CL-PPCRE comes with a system definition for ASDF and you compile and load it in the usual way. There are no dependencies (except that the test suite which is not needed for normal operation depends on FLEXI-STREAMS).

CL-PPCRE is integrated into the package/port systems of Debian, Gentoo, and FreeBSD, but before you install it from there, you should check if they actually offer the latest release. Installation via ASDF-Install should as well be possible.

You can run a test suite which tests most aspects of the library with

(asdf:oos 'asdf:test-op :cl-ppcre)

Luís Oliveira maintains a darcs repository of CL-PPCRE at http://common-lisp.net/~loliveira/ediware/.
 

Support and mailing lists

For questions, bug reports, feature requests, improvements, or patches please use the cl-ppcre-devel mailing list. If you want to be notified about future releases, subscribe to the cl-ppcre-announce mailing list. These mailing lists were made available thanks to the services of common-lisp.net. Terrence Brannon has created a Google group for the list which is at http://groups.google.com/group/cl-ppcre.

If you want to send patches, please read this first.
 

The CL-PPCRE dictionary

Scanning


[Method]
create-scanner (string string)&key case-insensitive-mode multi-line-mode single-line-mode extended-mode destructive => scanner, register-names


Accepts a string which is a regular expression in Perl syntax and returns a closure which will scan strings for this regular expression. The second value is only returned if *ALLOW-NAMED-REGISTERS* is true. It represents a list of strings mapping registers to their respective names - the first element stands for first register, the second element for second register, etc. You have to store this value if you want to map a register number to its name later as scanner doesn't capture any information about register names. If a register isn't named, it has NIL as its name.

The mode keyword arguments are equivalent to the "imsx" modifiers in Perl. The destructive keyword will be ignored.

The function accepts most of the regex syntax of Perl 5.8 as described in man perlre including extended features like non-greedy repetitions, positive and negative look-ahead and look-behind assertions, "standalone" subexpressions, and conditional subpatterns. The following Perl features are (currently) not supported:

  • (?{ code }) and (??{ code }) because they obviously don't make sense in Lisp.
  • \N{name} (named characters), \x{263a} (wide hex characters), \l, \u, \L, and \U because they're actually not part of Perl's regex syntax - but see CL-INTERPOL.
  • \X (extended Unicode), and \C (single character). But you can of course use all characters supported by your CL implementation.
  • Posix character classes like [[:alpha]]. Use Unicode properties instead.
  • \G for Perl's pos() because we don't have it.
Note, however, that \t, \n, \r, \f, \a, \e, \033 (octal character codes), \x1B (hexadecimal character codes), \c[ (control characters), \w, \W, \s, \S, \d, \D, \b, \B, \A, \Z, and \z are supported.

Since version 0.6.0, CL-PPCRE also supports Perl's \Q and \E - see *ALLOW-QUOTING* below. Make sure you also read the relevant section in "Bugs and problems."

Since version 1.3.0, CL-PPCRE offers support for AllegroCL's (?<name>"<regex>") named registers and \k<name> back-references syntax, have a look at *ALLOW-NAMED-REGISTERS* for details.

Since version 2.0.0, CL-PPCRE supports named properties (\p and \P), but only the long form with braces is supported, i.e. \p{Letter} and \p{L} will work while \pL won't.

The keyword arguments are just for your convenience. You can always use embedded modifiers like "(?i-s)" instead.


[Method]
create-scanner (function function)&key case-insensitive-mode multi-line-mode single-line-mode extended-mode destructive => scanner


In this case function should be a scanner returned by another invocation of CREATE-SCANNER. It will be returned as is. You can't use any of the keyword arguments because the scanner has already been created and is immutable.


[Method]
create-scanner (parse-tree t)&key case-insensitive-mode multi-line-mode single-line-mode extended-mode destructive => scanner, register-names


This is similar to CREATE-SCANNER for regex strings above but accepts a parse tree as its first argument. A parse tree is an S-expression conforming to the following syntax:
  • Every string and character is a parse tree and is treated literally as a part of the regular expression, i.e. parentheses, brackets, asterisks and such aren't special.
  • The symbol :VOID is equivalent to the empty string.
  • The symbol :EVERYTHING is equivalent to Perl's dot, i.e it matches everything (except maybe a newline character depending on the mode).
  • The symbols :WORD-BOUNDARY and :NON-WORD-BOUNDARY are equivalent to Perl's "\b" and "\B".
  • The symbols :DIGIT-CLASS, :NON-DIGIT-CLASS, :WORD-CHAR-CLASS, :NON-WORD-CHAR-CLASS, :WHITESPACE-CHAR-CLASS, and :NON-WHITESPACE-CHAR-CLASS are equivalent to Perl's special character classes "\d", "\D", "\w", "\W", "\s", and "\S" respectively.
  • The symbols :START-ANCHOR, :END-ANCHOR, :MODELESS-START-ANCHOR, :MODELESS-END-ANCHOR, and :MODELESS-END-ANCHOR-NO-NEWLINE are equivalent to Perl's "^", "$", "\A", "\Z", and "\z" respectively.
  • The symbols :CASE-INSENSITIVE-P, :CASE-SENSITIVE-P, :MULTI-LINE-MODE-P, :NOT-MULTI-LINE-MODE-P, :SINGLE-LINE-MODE-P, and :NOT-SINGLE-LINE-MODE-P are equivalent to Perl's embedded modifiers "(?i)", "(?-i)", "(?m)", "(?-m)", "(?s)", and "(?-s)". As usual, changes applied to modes are kept local to the innermost enclosing grouping or clustering construct.
  • All other symbols will signal an error of type PPCRE-SYNTAX-ERROR unless they are defined to be parse tree synonyms.
  • (:FLAGS {<modifier>}*) where <modifier> is one of the modifier symbols from above is used to group modifier symbols. The modifiers are applied from left to right. (This construct is obviously redundant. It is only there because it's used by the parser.)
  • (:SEQUENCE {<parse-tree>}*) means a sequence of parse trees, i.e. the parse trees must match one after another. Example: (:SEQUENCE #\f #\o #\o) is equivalent to the parse tree "foo".
  • (:GROUP {<parse-tree>}*) is like :SEQUENCE but changes applied to modifier flags (see above) are kept local to the parse trees enclosed by this construct. Think of it as the S-expression variant of Perl's "(?:<pattern>)" construct.
  • (:ALTERNATION {<parse-tree>}*) means an alternation of parse trees, i.e. one of the parse trees must match. Example: (:ALTERNATION #\b #\a #\z) is equivalent to the Perl regex string "b|a|z".
  • (:BRANCH <test> <parse-tree>) is for conditional regular expressions. <test> is either a number which stands for a register or a parse tree which is a look-ahead or look-behind assertion. See the entry for (?(<condition>)<yes-pattern>|<no-pattern>) in man perlre for the semantics of this construct. If <parse-tree> is an alternation is must enclose exactly one or two parse trees where the second one (if present) will be treated as the "no-pattern" - in all other cases <parse-tree> will be treated as the "yes-pattern".
  • (:POSITIVE-LOOKAHEAD|:NEGATIVE-LOOKAHEAD|:POSITIVE-LOOKBEHIND|:NEGATIVE-LOOKBEHIND <parse-tree>) should be pretty obvious...
  • (:GREEDY-REPETITION|:NON-GREEDY-REPETITION <min> <max> <parse-tree>) where <min> is a non-negative integer and <max> is either a non-negative integer not smaller than <min> or NIL will result in a regular expression which tries to match <parse-tree> at least <min> times and at most <max> times (or as often as possible if <max> is NIL). So, e.g., (:NON-GREEDY-REPETITION 0 1 "ab") is equivalent to the Perl regex string "(?:ab)??".
  • (:STANDALONE <parse-tree>) is an "independent" subexpression, i.e. (:STANDALONE "bar") is equivalent to the Perl regex string "(?>bar)".
  • (:REGISTER <parse-tree>) is a capturing register group. As usual, registers are counted from left to right beginning with 1.
  • (:NAMED-REGISTER <name> <parse-tree>) is a named capturing register group. Acts as :REGISTER, but assigns <name> to a register too. This <name> can be later referred to via :BACK-REFERENCE. Names are case-sensitive and don't need to be unique. See *ALLOW-NAMED-REGISTERS* for details.
  • (:BACK-REFERENCE <ref>) is a back-reference to a register group. <ref> is a positive integer or a string denoting a register name. If there are several registers with the same name, the regex engine tries to successfully match at least of them, starting with the most recently seen register continuing to the least recently seen one, until a match is found. See *ALLOW-NAMED-REGISTERS* for more information.
  • (:PROPERTY|:INVERTED-PROPERTY <property>) is a named property (or its inverse) with <property> being a function designator or a string which must be resolved by *PROPERTY-RESOLVER*.
  • (:FILTER <function> &optional <length>) where <function> is a function designator and <length> is a non-negative integer or NIL is a user-defined filter.
  • (:REGEX <string>) where <string> is an embedded regular expression in Perl syntax.
  • (:CHAR-CLASS|:INVERTED-CHAR-CLASS {<item>}*) where <item> is either a character, a character range, a named property (see above), or a symbol for a special character class (see above) will be translated into a (one character wide) character class. A character range looks like (:RANGE <char1> <char2>) where <char1> and <char2> are characters such that (CHAR<= <char1> <char2>) is true. Example: (:INVERTED-CHAR-CLASS #\a (:RANGE #\D #\G) :DIGIT-CLASS) is equivalent to the Perl regex string "[^aD-G\d]".
Because CREATE-SCANNER is defined as a generic function which dispatches on its first argument there's a certain ambiguity: Although strings are valid parse trees they will be interpreted as Perl regex strings when given to CREATE-SCANNER. To circumvent this you can always use the equivalent parse tree (:GROUP <string>) instead.

Note that CREATE-SCANNER doesn't always check for the well-formedness of its first argument, i.e. you are expected to provide correct parse trees.

The usage of the keyword argument extended-mode obviously doesn't make sense if CREATE-SCANNER is applied to parse trees and will signal an error.

If destructive is not NIL (the default is NIL), the function is allowed to destructively modify parse-tree while creating the scanner.

If you want to find out how parse trees are related to Perl regex strings, you should play around with PARSE-STRING:

* (parse-string "(ab)*")
(:GREEDY-REPETITION 0 NIL (:REGISTER "ab"))

* (parse-string "(a(b))")
(:REGISTER (:SEQUENCE #\a (:REGISTER #\b)))

* (parse-string "(?:abc){3,5}")
(:GREEDY-REPETITION 3 5 (:GROUP "abc"))
;; (:GREEDY-REPETITION 3 5 "abc") would also be OK

* (parse-string "a(?i)b(?-i)c")
(:SEQUENCE #\a
 (:SEQUENCE (:FLAGS :CASE-INSENSITIVE-P)
  (:SEQUENCE #\b (:SEQUENCE (:FLAGS :CASE-SENSITIVE-P) #\c))))
;; same as (:SEQUENCE #\a :CASE-INSENSITIVE-P #\b :CASE-SENSITIVE-P #\c)

* (parse-string "(?=a)b")
(:SEQUENCE (:POSITIVE-LOOKAHEAD #\a) #\b)


For the rest of the dictionary, regex can always be a string (which is interpreted as a Perl regular expression), a parse tree, or a scanner created by CREATE-SCANNER. The start and end keyword parameters are always used as in SCAN.


[Generic Function]
scan regex target-string &key start end => match-start, match-end, reg-starts, reg-ends


Searches the string target-string from start (which defaults to 0) to end (which default to the length of target-string) and tries to match regex. On success returns four values - the start of the match, the end of the match, and two arrays denoting the beginnings and ends of register matches. On failure returns NIL. target-string will be coerced to a simple string if it isn't one already. (There's another keyword parameter real-start-pos. This one should never be set from user code - it is only used internally.)

SCAN acts as if the part of target-string between start and end were a standalone string, i.e. look-aheads and look-behinds can't look beyond these boundaries.

* (scan "(a)*b" "xaaabd")
1
5
#(3)
#(4)

* (scan "(a)*b" "xaaabd" :start 1)
1
5
#(3)
#(4)

* (scan "(a)*b" "xaaabd" :start 2)
2
5
#(3)
#(4)

* (scan "(a)*b" "xaaabd" :end 4)
NIL

* (scan '(:greedy-repetition 0 nil #\b) "bbbc")
0
3
#()
#()

* (scan '(:greedy-repetition 4 6 #\b) "bbbc")
NIL

* (let ((s (create-scanner "(([a-c])+)x")))
    (scan s "abcxy"))
0
4
#(0 2)
#(3 3)


[Function]
scan-to-strings regex target-string &key start end sharedp => match, regs


Like SCAN but returns substrings of target-string instead of positions, i.e. this function returns two values on success: the whole match as a string plus an array of substrings (or NILs) corresponding to the matched registers. If sharedp is true, the substrings may share structure with target-string.
* (scan-to-strings "[^b]*b" "aaabd")
"aaab"
#()

* (scan-to-strings "([^b])*b" "aaabd")
"aaab"
#("a")

* (scan-to-strings "(([^b])*)b" "aaabd")
"aaab"
#("aaa" "a")


[Macro]
register-groups-bind var-list (regex target-string &key start end sharedp) declaration* statement* => result*


Evaluates statement* with the variables in var-list bound to the corresponding register groups after target-string has been matched against regex, i.e. each variable is either bound to a string or to NIL. As a shortcut, the elements of var-list can also be lists of the form (FN VAR) where VAR is the variable symbol and FN is a function designator (which is evaluated) denoting a function which is to be applied to the string before the result is bound to VAR. To make this even more convenient the form (FN VAR1 ...VARn) can be used as an abbreviation for (FN VAR1) ... (FN VARn).

If there is no match, the statement* forms are not executed. For each element of var-list which is NIL there's no binding to the corresponding register group. The number of variables in var-list must not be greater than the number of register groups. If sharedp is true, the substrings may share structure with target-string.

* (register-groups-bind (first second third fourth)
      ("((a)|(b)|(c))+" "abababc" :sharedp t)
    (list first second third fourth))
("c" "a" "b" "c")

* (register-groups-bind (nil second third fourth)
      ;; note that we don't bind the first and fifth register group
      ("((a)|(b)|(c))()+" "abababc" :start 6)
    (list second third fourth))
(NIL NIL "c")

* (register-groups-bind (first)
      ("(a|b)+" "accc" :start 1)
    (format t "This will not be printed: ~A" first))
NIL

* (register-groups-bind (fname lname (#'parse-integer date month year))
      ("(\\w+)\\s+(\\w+)\\s+(\\d{1,2})\\.(\\d{1,2})\\.(\\d{4})" "Frank Zappa 21.12.1940")
    (list fname lname (encode-universal-time 0 0 0 date month year 0)))
("Frank" "Zappa" 1292889600)


[Macro]
do-scans (match-start match-end reg-starts reg-ends regex target-string &optional result-form &key start end) declaration* statement* => result*


A macro which iterates over target-string and tries to match regex as often as possible evaluating statement* with match-start, match-end, reg-starts, and reg-ends bound to the four return values of each match (see SCAN) in turn. After the last match, returns result-form if provided or NIL otherwise. An implicit block named NIL surrounds DO-SCANS; RETURN may be used to terminate the loop immediately. If regex matches an empty string, the scan is continued one position behind this match.

This is the most general macro to iterate over all matches in a target string. See the source code of DO-MATCHES, ALL-MATCHES, SPLIT, or REGEX-REPLACE-ALL for examples of its usage.


[Macro]
do-matches (match-start match-end regex target-string &optional result-form &key start end) declaration* statement* => result*


Like DO-SCANS but doesn't bind variables to the register arrays.
* (defun foo (regex target-string &key (start 0) (end (length target-string)))
    (let ((sum 0))
      (do-matches (s e regex target-string nil :start start :end end)
        (incf sum (- e s)))
      (format t "~,2F% of the string was inside of a match~%"
                ;; note: doesn't check for division by zero
                (float (* 100 (/ sum (- end start)))))))

FOO

* (foo "a" "abcabcabc")
33.33% of the string was inside of a match
NIL
* (foo "aa|b" "aacabcbbc")
55.56% of the string was inside of a match
NIL


[Macro]
do-matches-as-strings (match-var regex target-string &optional result-form &key start end sharedp) declaration* statement* => result*


Like DO-MATCHES but binds match-var to the substring of target-string corresponding to each match in turn. If sharedp is true, the substrings may share structure with target-string.
* (defun crossfoot (target-string &key (start 0) (end (length target-string)))
    (let ((sum 0))
      (do-matches-as-strings (m :digit-class
                                         target-string nil
                                         :start start :end end)
        (incf sum (parse-integer m)))
      (if (< sum 10)
        sum
        (crossfoot (format nil "~A" sum)))))

CROSSFOOT

* (crossfoot "bar")
0

* (crossfoot "a3x")
3

* (crossfoot "12345")
6
Of course, in real life you would do this with DO-MATCHES and use the start and end keyword parameters of PARSE-INTEGER.


[Macro]
do-register-groups var-list (regex target-string &optional result-form &key start end sharedp) declaration* statement* => result*


Iterates over target-string and tries to match regex as often as possible evaluating statement* with the variables in var-list bound to the corresponding register groups for each match in turn, i.e. each variable is either bound to a string or to NIL. You can use the same shortcuts and abbreviations as in REGISTER-GROUPS-BIND. The number of variables in var-list must not be greater than the number of register groups. For each element of var-list which is NIL there's no binding to the corresponding register group. After the last match, returns result-form if provided or NIL otherwise. An implicit block named NIL surrounds DO-REGISTER-GROUPS; RETURN may be used to terminate the loop immediately. If regex matches an empty string, the scan is continued one position behind this match. If sharedp is true, the substrings may share structure with target-string.
* (do-register-groups (first second third fourth)
      ("((a)|(b)|(c))" "abababc" nil :start 2 :sharedp t)
    (print (list first second third fourth)))
("a" "a" NIL NIL) 
("b" NIL "b" NIL) 
("a" "a" NIL NIL) 
("b" NIL "b" NIL) 
("c" NIL NIL "c")
NIL

* (let (result)
    (do-register-groups ((#'parse-integer n) (#'intern sign) whitespace)
        ("(\\d+)|(\\+|-|\\*|/)|(\\s+)" "12*15 - 42/3")
      (unless whitespace
        (push (or n sign) result)))
    (nreverse result))
(12 * 15 - 42 / 3)


[Function]
all-matches regex target-string &key start end => list


Returns a list containing the start and end positions of all matches of regex against target-string, i.e. if there are N matches the list contains (* 2 N) elements. If regex matches an empty string the scan is continued one position behind this match.
* (all-matches "a" "foo bar baz")
(5 6 9 10)

* (all-matches "\\w*" "foo bar baz")
(0 3 3 3 4 7 7 7 8 11 11 11)


[Function]
all-matches-as-strings regex target-string &key start end sharedp => list


Like ALL-MATCHES but returns a list of substrings instead. If sharedp is true, the substrings may share structure with target-string.
* (all-matches-as-strings "a" "foo bar baz")
("a" "a")

* (all-matches-as-strings "\\w*" "foo bar baz")
("foo" "" "bar" "" "baz" "")

Splitting and replacing


[Function]
split regex target-string &key start end limit with-registers-p omit-unmatched-p sharedp => list


Matches regex against target-string as often as possible and returns a list of the substrings between the matches. If with-registers-p is true, substrings corresponding to matched registers are inserted into the list as well. If omit-unmatched-p is true, unmatched registers will simply be left out, otherwise they will show up as NIL. limit limits the number of elements returned - registers aren't counted. If limit is NIL (or 0 which is equivalent), trailing empty strings are removed from the result list. If regex matches an empty string, the scan is continued one position behind this match. If sharedp is true, the substrings may share structure with target-string.

This function also tries hard to be Perl-compatible - thus the somewhat peculiar behaviour.

* (split "\\s+" "foo   bar baz
frob")
("foo" "bar" "baz" "frob")

* (split "\\s*" "foo bar   baz")
("f" "o" "o" "b" "a" "r" "b" "a" "z")

* (split "(\\s+)" "foo bar   baz")
("foo" "bar" "baz")

* (split "(\\s+)" "foo bar   baz" :with-registers-p t)
("foo" " " "bar" "   " "baz")

* (split "(\\s)(\\s*)" "foo bar   baz" :with-registers-p t)
("foo" " " "" "bar" " " "  " "baz")

* (split "(,)|(;)" "foo,bar;baz" :with-registers-p t)
("foo" "," NIL "bar" NIL ";" "baz")

* (split "(,)|(;)" "foo,bar;baz" :with-registers-p t :omit-unmatched-p t)
("foo" "," "bar" ";" "baz")

* (split ":" "a:b:c:d:e:f:g::")
("a" "b" "c" "d" "e" "f" "g")

* (split ":" "a:b:c:d:e:f:g::" :limit 1)
("a:b:c:d:e:f:g::")

* (split ":" "a:b:c:d:e:f:g::" :limit 2)
("a" "b:c:d:e:f:g::")

* (split ":" "a:b:c:d:e:f:g::" :limit 3)
("a" "b" "c:d:e:f:g::")

* (split ":" "a:b:c:d:e:f:g::" :limit 1000)
("a" "b" "c" "d" "e" "f" "g" "" "")


[Function]
regex-replace regex target-string replacement &key start end preserve-case simple-calls element-type => string, matchp


Try to match target-string between start and end against regex and replace the first match with replacement. Two values are returned; the modified string, and T if regex matched or NIL otherwise.

replacement can be a string which may contain the special substrings "\&" for the whole match, "\`" for the part of target-string before the match, "\'" for the part of target-string after the match, "\N" or "\{N}" for the Nth register where N is a positive integer.

replacement can also be a function designator in which case the match will be replaced with the result of calling the function designated by replacement with the arguments target-string, start, end, match-start, match-end, reg-starts, and reg-ends. (reg-starts and reg-ends are arrays holding the start and end positions of matched registers (or NIL) - the meaning of the other arguments should be obvious.)

If simple-calls is true, a function designated by replacement will instead be called with the arguments match, register-1, ..., register-n where match is the whole match as a string and register-1 to register-n are the matched registers, also as strings (or NIL). Note that these strings share structure with target-string so you must not modify them.

Finally, replacement can be a list where each element is a string (which will be inserted verbatim), one of the symbols :match, :before-match, or :after-match (corresponding to "\&", "\`", and "\'" above), an integer N (representing register (1+ N)), or a function designator.

If preserve-case is true (default is NIL), the replacement will try to preserve the case (all upper case, all lower case, or capitalized) of the match. The result will always be a fresh string, even if regex doesn't match.

element-type specifies the array element type of the string which is returned, the default is LW:SIMPLE-CHAR for LispWorks and CHARACTER for other Lisps.

* (regex-replace "fo+" "foo bar" "frob")
"frob bar"
T

* (regex-replace "fo+" "FOO bar" "frob")
"FOO bar"
NIL

* (regex-replace "(?i)fo+" "FOO bar" "frob")
"frob bar"
T

* (regex-replace "(?i)fo+" "FOO bar" "frob" :preserve-case t)
"FROB bar"
T

* (regex-replace "(?i)fo+" "Foo bar" "frob" :preserve-case t)
"Frob bar"
T

* (regex-replace "bar" "foo bar baz" "[frob (was '\\&' between '\\`' and '\\'')]")
"foo [frob (was 'bar' between 'foo ' and ' baz')] baz"
T

* (regex-replace "bar" "foo bar baz"
                          '("[frob (was '" :match "' between '" :before-match "' and '" :after-match "')]"))
"foo [frob (was 'bar' between 'foo ' and ' baz')] baz"
T

* (regex-replace "(be)(nev)(o)(lent)"
                          "benevolent: adj. generous, kind"
                          #'(lambda (match &rest registers)
                              (format nil "~A [~{~A~^.~}]" match registers))
                          :simple-calls t)
"benevolent [be.nev.o.lent]: adj. generous, kind"
T


[Function]
regex-replace-all regex target-string replacement &key start end preserve-case simple-calls element-type => string, matchp


Like REGEX-REPLACE but replaces all matches.
* (regex-replace-all "(?i)fo+" "foo Fooo FOOOO bar" "frob" :preserve-case t)
"frob Frob FROB bar"
T

* (regex-replace-all "(?i)f(o+)" "foo Fooo FOOOO bar" "fr\\1b" :preserve-case t)
"froob Frooob FROOOOB bar"
T

* (let ((qp-regex (create-scanner "[\\x80-\\xff]")))
    (defun encode-quoted-printable (string)
      "Converts 8-bit string to quoted-printable representation."
      ;; won't work for Corman Lisp because non-ASCII characters aren't 8-bit there
      (flet ((convert (target-string start end match-start match-end reg-starts reg-ends)
             (declare (ignore start end match-end reg-starts reg-ends))
             (format nil "=~2,'0x" (char-code (char target-string match-start)))))
        (regex-replace-all qp-regex string #'convert))))
Converted ENCODE-QUOTED-PRINTABLE.
ENCODE-QUOTED-PRINTABLE

* (encode-quoted-printable "Fête Sørensen naïve Hühner Straße")
"F=EAte S=F8rensen na=EFve H=FChner Stra=DFe"
T

* (let ((url-regex (create-scanner "[^a-zA-Z0-9_\\-.]")))
    (defun url-encode (string)
      "URL-encodes a string."
      ;; won't work for Corman Lisp because non-ASCII characters aren't 8-bit there
      (flet ((convert (target-string start end match-start match-end reg-starts reg-ends)
             (declare (ignore start end match-end reg-starts reg-ends))
             (format nil "%~2,'0x" (char-code (char target-string match-start)))))
        (regex-replace-all url-regex string #'convert))))
Converted URL-ENCODE.
URL-ENCODE

* (url-encode "Fête Sørensen naïve Hühner Straße")
"F%EAte%20S%F8rensen%20na%EFve%20H%FChner%20Stra%DFe"
T

* (defun how-many (target-string start end match-start match-end reg-starts reg-ends)
    (declare (ignore start end match-start match-end))
    (format nil "~A" (- (svref reg-ends 0)
                        (svref reg-starts 0))))
HOW-MANY

* (regex-replace-all "{(.+?)}"
                              "foo{...}bar{.....}{..}baz{....}frob"
                              (list "[" 'how-many " dots]"))
"foo[3 dots]bar[5 dots][2 dots]baz[4 dots]frob"
T

* (let ((qp-regex (create-scanner "[\\x80-\\xff]")))
    (defun encode-quoted-printable (string)
      "Converts 8-bit string to quoted-printable representation.
Version using SIMPLE-CALLS keyword argument."
      ;; ;; won't work for Corman Lisp because non-ASCII characters aren't 8-bit there
      (flet ((convert (match)
               (format nil "=~2,'0x" (char-code (char match 0)))))
        (regex-replace-all qp-regex string #'convert
                                    :simple-calls t))))

Converted ENCODE-QUOTED-PRINTABLE.
ENCODE-QUOTED-PRINTABLE

* (encode-quoted-printable "Fête Sørensen naïve Hühner Straße")
"F=EAte S=F8rensen na=EFve H=FChner Stra=DFe"
T

* (defun how-many (match first-register)
    (declare (ignore match))
    (format nil "~A" (length first-register)))
HOW-MANY

* (regex-replace-all "{(.+?)}"
                              "foo{...}bar{.....}{..}baz{....}frob"
                              (list "[" 'how-many " dots]")
                              :simple-calls t)

"foo[3 dots]bar[5 dots][2 dots]baz[4 dots]frob"
T

Modifying scanner behaviour


[Special variable]
*property-resolver*


This is the designator for a function responsible for resolving named properties like \p{Number}. If CL-PPCRE encounters a \p or a \P it expects to see an opening curly brace immediately afterwards and will then read everything following that brace until it sees a closing curly brace. The resolver function will be called with this string and must return a corresponding unary test function which accepts a character as its argument and returns a true value if and only if the character has the named property. If the resolver returns NIL instead, it signals that a property of that name is unknown.
* (labels ((char-code-odd-p (char)
             (oddp (char-code char)))
           (char-code-even-p (char)
             (evenp (char-code char)))
           (resolver (name)
             (cond ((string= name "odd") #'char-code-odd-p)
                   ((string= name "even") #'char-code-even-p)
                   ((string= name "true") (constantly t))
                   (t (error "Can't resolve ~S." name)))))
    (let ((*property-resolver* #'resolver))
      ;; quiz question - why do we need CREATE-SCANNER here?
      (list (regex-replace-all (create-scanner "\\p{odd}") "abcd" "+")
            (regex-replace-all (create-scanner "\\p{even}") "abcd" "+")
            (regex-replace-all (create-scanner "\\p{true}") "abcd" "+"))))
("+b+d" "a+c+" "++++")
If the value of *PROPERTY-RESOLVER* is NIL (which is the default), \p and \P in regex strings will simply be treated like p or P as in CL-PPCRE 1.4.1 and earlier. Note that this does not affect the validity of (:PROPERTY <name>) parts in S-expression syntax.


[Accessor]
parse-tree-synonym symbol => parse-tree
(setf (parse-tree-synonym symbol) new-parse-tree)


Any symbol (unless it's a keyword with a special meaning in parse trees) can be made a "synonym", i.e. an abbreviation, for another parse tree by this accessor. PARSE-TREE-SYNONYM returns NIL if symbol isn't a synonym yet.
* (parse-string "a*b+")
(:SEQUENCE (:GREEDY-REPETITION 0 NIL #\a) (:GREEDY-REPETITION 1 NIL #\b))

* (defun my-repetition (char min)
    `(:greedy-repetition ,min nil ,char))
MY-REPETITION

* (setf (parse-tree-synonym 'a*) (my-repetition #\a 0))
(:GREEDY-REPETITION 0 NIL #\a)

* (setf (parse-tree-synonym 'b+) (my-repetition #\b 1))
(:GREEDY-REPETITION 1 NIL #\b)

* (let ((scanner (create-scanner '(:sequence a* b+))))
    (dolist (string '("ab" "b" "aab" "a" "x"))
      (print (scan scanner string)))
    (values))
0
0
0
NIL
NIL

* (parse-tree-synonym 'a*)
(:GREEDY-REPETITION 0 NIL #\a)

* (parse-tree-synonym 'a+)
NIL


[Macro]
define-parse-tree-synonym name parse-tree => parse-tree


This is a convenience macro for parse tree synonyms defined as
(defmacro define-parse-tree-synonym (name parse-tree)
  `(eval-when (:compile-toplevel :load-toplevel :execute)
     (setf (parse-tree-synonym ',name) ',parse-tree)))
so you can write code like this:
(define-parse-tree-synonym a-z
  (:char-class (:range #\a #\z) (:range #\A #\Z)))

(define-parse-tree-synonym a-z*
  (:greedy-repetition 0 nil a-z))

(defun ascii-char-tester (string)
  (scan '(:sequence :start-anchor a-z* :end-anchor)
        string))


[Special variable]
*regex-char-code-limit*


This variable controls whether scanners take into account all characters of your CL implementation or only those the CHAR-CODE of which is not larger than its value. The default is CHAR-CODE-LIMIT, and you might see significant speed and space improvements during scanner creation if, say, your target strings only contain ISO-8859-1 characters and you're using a Lisp implementation where CHAR-CODE-LIMIT has a value much higher than 256. The test suite will automatically set *REGEX-CHAR-CODE-LIMIT* to 256 while you're running the default test.

Note: Due to the nature of LOAD-TIME-VALUE and the compiler macro for SCAN and other functions, some scanners might be created in a null lexical environment at load time or at compile time so be careful to which value *REGEX-CHAR-CODE-LIMIT* is bound at that time. The default value should always yield correct results unless you play dirty tricks with implementation-dependent behaviour, though.


[Special variable]
*use-bmh-matchers*


Usually, the scanners created by CREATE-SCANNER (or implicitly by other functions and macros) will use the standard function SEARCH to check for constant strings at the start or end of the regular expression. If *USE-BMH-MATCHERS* is true (the default is NIL), fast Boyer-Moore-Horspool matchers will be used instead. This will usually be faster but can make the scanners considerably bigger. Per BMH matcher - there can be up to two per scanner - a fixnum array of size *REGEX-CHAR-CODE-LIMIT* is allocated and closed over.

Note: Due to the nature of LOAD-TIME-VALUE and the compiler macro for SCAN and other functions, some scanners might be created in a null lexical environment at load time or at compile time so be careful to which value *USE-BMH-MATCHERS* is bound at that time.


[Special variable]
*optimize-char-classes*


Whether character classes should be compiled into look-ups into O(1) data structures. This is usually fast but will be costly in terms of scanner creation time and might be costly in terms of size if *REGEX-CHAR-CODE-LIMIT* is high. This value will be used as the kind keyword argument to CREATE-OPTIMIZED-TEST-FUNCTION - see there for the possible non-NIL values. The default value (NIL) should usually be fine unless you're sure that you absolutely have to optimize some character classes for speed.

Note: Due to the nature of LOAD-TIME-VALUE and the compiler macro for SCAN and other functions, some scanners might be created in a null lexical environment at load time or at compile time so be careful to which value *OPTIMIZE-CHAR-CLASSES* is bound at that time.


[Special variable]
*allow-quoting*


If this value is true (the default is NIL), CL-PPCRE will support \Q and \E in regex strings to quote (disable) metacharacters. Note that this entails a slight performance penalty when creating scanners because (a copy of) the regex string is modified (probably more than once) before it is fed to the parser. Also, the parser's syntax error messages will complain about the converted string and not about the original regex string.
* (scan "^a+$" "a+")
NIL

* (let ((*allow-quoting* t))
    ;;we use CREATE-SCANNER because of Lisps like SBCL that don't have an interpreter
    (scan (create-scanner "^\\Qa+\\E$") "a+"))
0
2
#()
#()

* (let ((*allow-quoting* t))
    (scan (create-scanner "\\Qa()\\E(?#comment\\Q)a**b") "()ab"))

Quantifier '*' not allowed at position 19 in string "a\\(\\)(?#commentQ)a**b"
Note how in the last example the regex string in the error message is different from the first argument to the SCAN function. Also note that the second example might be easier to understand (and Lisp-ier) if you write it like this:
* (scan '(:sequence :start-anchor
                    "a+" ;; no quoting necessary
                    :end-anchor)
        "a+")
0
2
#()
#()
Make sure you also read the relevant section in "Bugs and problems."

Note: Due to the nature of LOAD-TIME-VALUE and the compiler macro for SCAN and other functions, some scanners might be created in a null lexical environment at load time or at compile time so be careful to which value *ALLOW-QUOTING* is bound at that time.


[Special variable]
*allow-named-registers*


If this value is true (the default is NIL), CL-PPCRE will support (?<name>"<regex>") and \k<name> in regex strings to provide named registers and back-references as in AllegroCL. name is has to start with a letter and can contain only alphanumeric characters or minus sign. Names of registers are matched case-sensitively. The parse tree syntax is not affected by the *ALLOW-NAMED-REGISTERS* switch, :NAMED-REGISTER and :BACK-REFERENCE forms are always resolved as expected. There are also no restrictions on register names in this syntax except that they have to be strings.
;; Perl compatible mode (*ALLOW-NAMED-REGISTERS* is NIL)
* (create-scanner "(?<reg>.*)")
Character 'r' may not follow '(?<' at position 3 in string "(?<reg>)"

;; just unescapes "\\k"
* (parse-string "\\k<reg>")
"k<reg>"

* (setq *allow-named-registers* t)
T

* (create-scanner "((?<small>[a-z]*)(?<big>[A-Z]*))")
#<CLOSURE (LAMBDA (STRING CL-PPCRE::START CL-PPCRE::END)) {AD75BFD}>
(NIL "small" "big")

;; the scanner doesn't capture any information about named groups -
;; you have to store the second value returned from CREATE-SCANNER yourself
* (scan * "aaaBBB")
0
6
#(0 0 3)
#(6 3 6)

;; parse tree syntax
* (parse-string "((?<small>[a-z]*)(?<big>[A-Z]*))")
(:REGISTER
 (:SEQUENCE
  (:NAMED-REGISTER "small"
   (:GREEDY-REPETITION 0 NIL (:CHAR-CLASS (:RANGE #\a #\z))))
  (:NAMED-REGISTER "big"
   (:GREEDY-REPETITION 0 NIL (:CHAR-CLASS (:RANGE #\A #\Z))))))

* (create-scanner *)
#<CLOSURE (LAMBDA (STRING CL-PPCRE::START CL-PPCRE::END)) {B158E3D}>
(NIL "small" "big")

;; multiple-choice back-reference
* (scan "^(?<reg>[ab])(?<reg>[12])\\k<reg>\\k<reg>$" "a1aa")
0
4
#(0 1)
#(1 2)

* (scan "^(?<reg>[ab])(?<reg>[12])\\k<reg>\\k<reg>$" "a22a")
0
4
#(0 1)
#(1 2)

;; demonstrating most-recently-seen-register-first property of back-reference;
;; "greedy" regex (analogous to "aa?")
* (scan "^(?<reg>)(?<reg>a)(\\k<reg>)" "a")
0
1
#(0 0 1)
#(0 1 1)

* (scan "^(?<reg>)(?<reg>a)(\\k<reg>)" "aa")
0
2
#(0 0 1)
#(0 1 2)

;; switched groups
;; "lazy" regex (analogous to "aa??")
* (scan "^(?<reg>a)(?<reg>)(\\k<reg>)" "a")
0
1
#(0 1 1)
#(1 1 1)

;; scanner ignores the second "a"
* (scan "^(?<reg>a)(?<reg>)(\\k<reg>)" "aa")
0
1
#(0 1 1)
#(1 1 1)

;; "aa" will be matched only when forced by adding "$" at the end
* (scan "^(?<reg>a)(?<reg>)(\\k<reg>)$" "aa")
0
2
#(0 1 1)
#(1 1 2)
Note: Due to the nature of LOAD-TIME-VALUE and the compiler macro for SCAN and other functions, some scanners might be created in a null lexical environment at load time or at compile time so be careful to which value *ALLOW-NAMED-REGISTERS* is bound at that time.

Miscellaneous


[Function]
parse-string string => parse-tree


Converts the regex string string into a parse tree. Note that the result is usually one possible way of creating an equivalent parse tree and not necessarily the "canonical" one. Specifically, the parse tree might contain redundant parts which are supposed to be excised when a scanner is created.


[Function]
create-optimized-test-function test-function &key start end kind => function


Given a unary test function test-function which is applicable to characters returns a function which yields the same boolean results for all characters with character codes from start to (excluding) end. If kind is NIL, test-function will simply be returned. Otherwise, kind should be one of:
:HASH-TABLE
The function builds a hash table representing all characters which satisfy the test and returns a closure which checks if a character is in that hash table.
:CHARSET
Instead of a hash table the function uses a "charset" which is a data structure using non-linear hashing and optimized to represent (sparse) sets of characters in a fast and space-efficient way (contributed by Nikodemus Siivola).
:CHARMAP
Instead of a hash table the function uses a bit vector to represent the set of characters.
You can also use :HASH-TABLE* or :CHARSET* which are like :HASH-TABLE and :CHARSET but use the complement of the set if the set contains more than half of all characters between start and end. This saves space but needs an additional pass across all characters to create the data structure. There is no corresponding :CHARMAP* kind as the bit vectors are already created to cover the smallest possible interval which contains either the set or its complement.

See also *OPTIMIZE-CHAR-CLASSES*.


[Function]
quote-meta-chars string => string'


This is a simple utility function used when *ALLOW-QUOTING* is true. It returns a string STRING' where all non-word characters (everything except ASCII characters, digits and underline) of STRING are quoted by prepending a backslash similar to Perl's quotemeta function. It always returns a fresh string.
* (quote-meta-chars "[a-z]*")
"\\[a\\-z\\]\\*"


[Function]
regex-apropos regex &optional packages &key case-insensitive => list


Like APROPOS but searches for interned symbols which match the regular expression regex. The output is implementation-dependent. If case-insensitive is true (which is the default) and regex isn't already a scanner, a case-insensitive scanner is used.

Here are examples for CMUCL:

* *package*
#<The COMMON-LISP-USER package, 16/21 internal, 0/9 external>

* (defun foo (n &optional (k 0)) (+ 3 n k))
FOO

* (defparameter foo "bar")
FOO

* (defparameter |foobar| 42)
|foobar|

* (defparameter fooboo 43)
FOOBOO

* (defclass frobar () ())
#<STANDARD-CLASS FROBAR {4874E625}>

* (regex-apropos "foo(?:bar)?")
FOO [variable] value: "bar"
    [compiled function] (N &OPTIONAL (K 0))
FOOBOO [variable] value: 43
|foobar| [variable] value: 42

* (regex-apropos "(?:foo|fro)bar")
PCL::|COMMON-LISP-USER::FROBAR class predicate| [compiled closure]
FROBAR [class] #<STANDARD-CLASS FROBAR {4874E625}>
|foobar| [variable] value: 42

* (regex-apropos "(?:foo|fro)bar" 'cl-user)
FROBAR [class] #<STANDARD-CLASS FROBAR {4874E625}>
|foobar| [variable] value: 42

* (regex-apropos "(?:foo|fro)bar" '(pcl ext))
PCL::|COMMON-LISP-USER::FROBAR class predicate| [compiled closure]

* (regex-apropos "foo")
FOO [variable] value: "bar"
    [compiled function] (N &OPTIONAL (K 0))
FOOBOO [variable] value: 43
|foobar| [variable] value: 42

* (regex-apropos "foo" nil :case-insensitive nil)
|foobar| [variable] value: 42


[Function]
regex-apropos-list regex &optional packages &key upcase => list


Like APROPOS-LIST but searches for interned symbols which match the regular expression regex. If case-insensitive is true (which is the default) and regex isn't already a scanner, a case-insensitive scanner is used.

Example (continued from above):

* (regex-apropos-list "foo(?:bar)?")
(|foobar| FOOBOO FOO)

Conditions


[Condition type]
ppcre-error


Every error signaled by CL-PPCRE is of type PPCRE-ERROR. This is a direct subtype of SIMPLE-ERROR without any additional slots or options.


[Condition type]
ppcre-invocation-error


Errors of type PPCRE-INVOCATION-ERROR are signaled if one of the exported functions of CL-PPCRE is called with wrong or inconsistent arguments. This is a direct subtype of PPCRE-ERROR without any additional slots or options.


[Condition type]
ppcre-syntax-error


An error of type PPCRE-SYNTAX-ERROR is signaled if CL-PPCRE's parser encounters an error when trying to parse a regex string or to convert a parse tree into its internal representation. This is a direct subtype of PPCRE-ERROR with two additional slots. These denote the regex string which HTML-PPCRE was parsing and the position within the string where the error occurred. If the error happens while CL-PPCRE is converting a parse tree, both of these slots contain NIL. (See the next two entries on how to access these slots.)

As many syntax errors can't be detected before the parser is at the end of the stream, the row and column usually denote the last position where the parser was happy and not the position where it gave up.

* (handler-case
    (scan "foo**x" "fooox")
    (ppcre-syntax-error (condition)
      (format t "Houston, we've got a problem with the string ~S:~%~
                 Looks like something went wrong at position ~A.~%~
                 The last message we received was \"~?\"."
              (ppcre-syntax-error-string condition)
              (ppcre-syntax-error-pos condition)
              (simple-condition-format-control condition)
              (simple-condition-format-arguments condition))
      (values)))
Houston, we've got a problem with the string "foo**x":
Looks like something went wrong at position 4.
The last message we received was "Quantifier '*' not allowed.".


[Function]
ppcre-syntax-error-string condition => string


If condition is a condition of type PPCRE-SYNTAX-ERROR, this function will return the string the parser was parsing when the error was encountered (or NIL if the error happened while trying to convert a parse tree). This might be particularly useful when *ALLOW-QUOTING* is true because in this case the offending string might not be the one you gave to the CREATE-SCANNER function.


[Function]
ppcre-syntax-error-pos condition => number


If condition is a condition of type PPCRE-SYNTAX-ERROR, this function will return the position within the string where the error occurred (or NIL if the error happened while trying to convert a parse tree).

 

Unicode properties

You can add support for Unicode properties to CL-PPCRE by loading the CL-PPCRE-UNICODE system (which depends on CL-UNICODE):
(asdf:oos 'asdf:load-op :cl-ppcre-unicode)
This will automatically install UNICODE-PROPERTY-RESOLVER as your property resolver.

See the CL-UNICODE documentation for information about the supported Unicode properties and how they are named.


[Function]
unicode-property-resolver property-name => function-or-nil


A property resolver which understands Unicode properties using CL-UNICODE's PROPERTY-TEST function. This resolver is automatically installed in *PROPERTY-RESOLVER* when the CL-PPCRE-UNICODE system is loaded.
* (scan-to-strings "\\p{Script:Latin}+" "0+AB_*")
"AB"
#()
Note that this symbol is exported from the CL-PPCRE-UNICODE package and not from the CL-PPCRE package.

 

Filters

Because several users have asked for it, CL-PPCRE now offers "filters" (see above for syntax) which are basically arbitrary, user-defined functions that can act as regex building blocks. Filters can only be used within parse trees, not within Perl regex strings.

A filter is defined by its filter function which must be a function of one argument. During the parsing process this function might be called once or several times or it might not be called at all. If it's called, its argument is an integer pos which is the current position within the target string. The filter can either return NIL (which means that the subexpression represented by this filter didn't match) or an integer not smaller than pos for success. A zero-length assertion should return pos itself while a filter which wants to consume N characters should return (+ POS N).

If you supply the optional value length and it is not NIL, then this is a promise to the regex engine that your filter will always consume exactly length characters. The regex engine might use this information for optimization purposes but it is otherwise irrelevant to the outcome of the matching process.

The filter function can access the following special variables from its code body:

CL-PPCRE::*STRING*
The target (a string) of the current matching process.
CL-PPCRE::*START-POS* and CL-PPCRE::*END-POS*
The start and end (integers) indices of the current matching process. These correspond to the START and END keyword parameters of SCAN.
CL-PPCRE::*REAL-START-POS*
The initial starting position. This is only relevant for repeated scans (as in DO-SCANS) where CL-PPCRE::*START-POS* will be moved forward while CL-PPCRE::*REAL-START-POS* won't. For normal scans the value of this variable is NIL.
CL-PPCRE::*REG-STARTS* and CL-PPCRE::*REG-ENDS*
Two simple vectors which denote the start and end indices of registers within the regular expression. The first register is indexed by 0. If a register hasn't matched yet, then its corresponding entry in CL-PPCRE::*REG-STARTS* is NIL.
These variables should be considered read-only. Do not change these values unless you really know what you're doing!

Note that the names of the variables are not exported from the CL-PPCRE package because there's no explicit guarantee that they will be available in future releases. (Although after so many years it is very unlikely that they'll go away...)

* (defun my-info-filter (pos)
    "Show some info about the matching process."
    (format t "Called at position ~A~%" pos)
    (loop with dim = (array-dimension cl-ppcre::*reg-starts* 0)
          for i below dim
          for reg-start = (aref cl-ppcre::*reg-starts* i)
          for reg-end = (aref cl-ppcre::*reg-ends* i)
          do (format t "Register ~A is currently " (1+ i))
          when reg-start
               (write-string cl-ppcre::*string* nil
            do (write-char #\')
               (write-string cl-ppcre::*string* nil
                     :start reg-start :end reg-end)
               (write-char #\')
          else
            do (write-string "unbound")
          do (terpri))
    (terpri)
    pos)
MY-INFO-FILTER

* (scan '(:sequence
           (:register
             (:greedy-repetition 0 nil
                                 (:char-class (:range #\a #\z))))
           (:filter my-info-filter 0) "X")
        "bYcdeX")
Called at position 1
Register 1 is currently 'b'

Called at position 0
Register 1 is currently ''

Called at position 1
Register 1 is currently ''

Called at position 5
Register 1 is currently 'cde'

2
6
#(2)
#(5)

* (scan '(:sequence
           (:register
             (:greedy-repetition 0 nil
                                 (:char-class (:range #\a #\z))))
           (:filter my-info-filter 0) "X")
        "bYcdeZ")
NIL

* (defun my-weird-filter (pos)
    "Only match at this point if either pos is odd and the character
  we're looking at is lowercase or if pos is even and the next two
  characters we're looking at are uppercase. Consume these characters if
  there's a match."
    (format t "Trying at position ~A~%" pos)
    (cond ((and (oddp pos)
                (< pos cl-ppcre::*end-pos*)
                (lower-case-p (char cl-ppcre::*string* pos)))
           (1+ pos))
          ((and (evenp pos)
                (< (1+ pos) cl-ppcre::*end-pos*)
                (upper-case-p (char cl-ppcre::*string* pos))
                (upper-case-p (char cl-ppcre::*string* (1+ pos))))
           (+ pos 2))
          (t nil)))
MY-WEIRD-FILTER

* (defparameter *weird-regex*
                `(:sequence "+" (:filter ,#'my-weird-filter) "+"))
*WEIRD-REGEX*

* (scan *weird-regex* "+A++a+AA+")
Trying at position 1
Trying at position 3
Trying at position 4
Trying at position 6
5
9
#()
#()

* (fmakunbound 'my-weird-filter)
MY-WEIRD-FILTER

* (scan *weird-regex* "+A++a+AA+")
Trying at position 1
Trying at position 3
Trying at position 4
Trying at position 6
5
9
#()
#()
Note that in the second call to SCAN our filter wasn't invoked at all - it was optimized away by the regex engine because it knew that it couldn't match. Also note that *WEIRD-REGEX* still worked after we removed the global function definition of MY-WEIRD-FILTER because the regular expression had captured the original definition.

For more ideas about what you can do with filters see this thread on the mailing list.
 

Compatibility with Perl

Depending on your Perl version you might encounter a couple of small incompatibilities with Perl most of which aren't due to CL-PPCRE:

Empty strings instead of undef in $1, $2, etc.

(Cf. case #629 of perltestdata.) This is a bug in Perl 5.6.1 and earlier which has been fixed in 5.8.0.

Strange scoping of embedded modifiers

(Cf. case #430 of perltestdata.) This is a bug in Perl 5.6.1 and earlier which has been fixed in 5.8.0.

Inconsistent capturing of $1, $2, etc.

(Cf. case #662 of perltestdata.) This is a bug in Perl which hasn't been fixed yet.

Captured groups not available outside of look-aheads and look-behinds

(Cf. case #1439 of perltestdata.) Well, OK, this ain't a Perl bug. I just can't quite understand why captured groups should only be seen within the scope of a look-ahead or look-behind. For the moment, CL-PPCRE and Perl agree to disagree... :)

Alternations don't always work from left to right

(Cf. case #790 of perltestdata.) I also think this a Perl bug but I currently have lost the drive to report it.

Different names for Unicode properties

The names of Unicode properties are derived from CL-UNICODE and might differ slightly from the names in Perl. Most of them should be identical, though. Also, CL-UNICODE is based on Unicode 5.1 while your installed Perl version might be not.

"\r" doesn't work with MCL

(Cf. case #9 of perltestdata.) For some strange reason that I don't understand MCL translates #\Return to (CODE-CHAR 10) while MacPerl translates "\r" to (CODE-CHAR 13). Hmmm...

What about "\w"?

CL-PPCRE uses ALPHANUMERICP to decide whether a character matches Perl's "\w", so depending on your CL implementation you might encounter differences between Perl and CL-PPCRE when matching non-ASCII characters.
 

Bugs and problems

"\Q" doesn't work, or does it?

In Perl the following code works as expected, i.e. it prints 1.
#!/usr/bin/perl -l

$a = '\E*';
print 1
  if '\E*\E*' =~ /(?:\Q$a\E){2}/;
If you try to do something similar in CL-PPCRE, you get an error:
* (let ((*allow-quoting* t)
        (a "\\E*"))
    (scan (concatenate 'string "(?:\\Q" a "\\E){2}") "\\E*\\E*"))
Quantifier '*' not allowed at position 3 in string "(?:*\\E){2}"
The error message might give you a hint as to why this happens: Because *ALLOW-QUOTING* was true the concatenated string was pre-processed before it was fed to CL-PPCRE's parser - the result of this pre-processing is "(?:*\\E){2}" because the "\\E" in the string A was taken to be the end of the quoted section started by "\\Q". This cannot happen in Perl due to its complicated interpolation rules - see man perlop for the scary details. It can happen in CL-PPCRE, though. Bummer!

What gives? "\\Q...\\E" in CL-PPCRE should only be used in literal strings. If you want to quote arbitrary strings, try CL-INTERPOL or use QUOTE-META-CHARS:

* (let ((a "\\E*"))
    (scan (concatenate 'string "(?:" (quote-meta-chars a) "){2}") "\\E*\\E*"))
0
6
#()
#()
Or, even better and Lisp-ier, use the S-expression syntax instead - no need for quoting in this case:
* (let ((a "\\E*"))
    (scan `(:greedy-repetition 2 2 ,a) "\\E*\\E*"))
0
6
#()
#()

Backslashes may confuse you...

* (let ((a "y\\y"))
    (scan a a))
NIL
You didn't expect this to yield NIL, did you? Shouldn't something like (SCAN A A) always return a true value? No, because the first and the second argument to SCAN are handled differently: The first argument is fed to CL-PPCRE's parser and is treated like a Perl regular expression. In particular, the parser "sees" \y and converts it to y because \y has no special meaning in regular expressions. So, the regular expression is the constant string "yy". But the second argument isn't converted - it is left as is, i.e. it's equivalent to Perl's 'y\y'. In other words, this example would be equivalent to the Perl code
'y\y' =~ /y\y/;
or to
$a = 'y\y';
$a =~ /$a/;
which should explain why it doesn't match.

Still confused? You might want to try CL-INTERPOL.
 

AllegroCL compatibility mode

Since autumn 2004 AllegroCL offers a new regular expression API with a syntax very similar to CL-PPCRE. Although CL-PPCRE is quite fast already, AllegroCL's engine will most likely be even faster (but only on AllegroCL, of course). However, you might want to stick to CL-PPCRE because you have a "legacy" application or because you want your code to be portable to other Lisp implementations. Therefore, beginning from version 1.2.0, CL-PPCRE offers a "compatibility mode" where you can continue using the CL-PPCRE API as described above but deploy the AllegroCL regex engine under the hood. (The details are: Calls to CREATE-SCANNER and SCAN are dispatched to their AllegroCL counterparts EXCL:COMPILE-RE and EXCL:MATCH-RE while everything else is left as is.)

The advantage of this mode is that you'll get a much smaller image and most likely faster code. (But note that CL-PPCRE needs to do a small amount of work to massage AllegroCL's output into the format expected by CL-PPCRE.) The downside is that your code won't be fully compatible with CL-PPCRE anymore. Here are some of the differences (most of which probably don't matter very often):

For more details about the AllegroCL engine and possible deviations from CL-PPCRE see the documentation at the Franz Inc. website.

To use the AllegroCL compatibility mode you have to

(push :use-acl-regexp2-engine *features*)
before you compile CL-PPCRE.
 

Hints, comments, performance considerations

Here are, in no particular order, a couple of things about CL-PPCRE and regular expressions in general that you might or might not want to read.
  • A lot of hackers (especially users of Perl and other scripting languages) think that regular expressions are the greatest thing since slice bread and use it for almost everything. That is just plain wrong. Other hackers (especially Lispers) tend to think that regular expressions are the work of the devil and try to avoid them at all cost. That's also wrong. Regular expressions are a handy and useful addition to your toolkit which you should use when appropriate - you should just try to figure out first if they're appropriate for the task at hand.
  • If you're concerned about the string syntax of regular expressions which can look like line noise and is really hard to read for long expressions, consider using CL-PPCRE's S-expression syntax instead. It is less error-prone and you don't have to worry about escaping characters. It is also easier to manipulate programmatically.
  • For alternations, order is important. The general rule is that the regex engine tries from left to right and tries to match as much as possible.
    CL-USER 1 > (scan-to-strings "<=|<" "<=")
    "<="
    #()
    
    CL-USER 2 > (scan-to-strings "<|<=" "<=")
    "<"
    #()
    
  • CL-PPCRE uses compiler macros to pre-compile scanners at load time if possible. This happens if the compiler can determine that the regular expression (no matter if it's a string or an S-expression) is constant at compile time and is intended to save the time for creating scanners at execution time (probably creating the same scanner over and over in a loop). Make sure you don't prevent the compiler from helping you. For example, a definition like this one is usually not a good idea:
    (defun regex-match (regex target)
      ;; don't do that!
      (scan regex target))
    
  • If you want to search for a substring in a large string or if you search for the same string very often, SCAN will usually be faster than Common Lisp's SEARCH if you use BMH matchers. However, this only makes sense if scanner creation time is not the limiting factor, i.e. if the search target is very large or if you're using the same scanner very often.
  • Complementary to the last hint, don't use regular expressions for one-time searches for constant strings. That's a terrible waste of resources.
  • *USE-BMH-MATCHERS* together with a large value for *REGEX-CHAR-CODE-LIMIT* can lead to huge scanners.
  • A character class is by default translated into a sequence of tests exactly as you might expect. For example, "[af-l\\d]" means to test if the character is equal to #\a, then to test if it's between #\f and #\l, then if it's a digit. There's by default no attempt to remove redundancy (as in "[a-ge-kf]") or to otherwise optimize these tests for speed. However, you can play with *OPTIMIZE-CHAR-CLASSES* if you've identified character classes as a bottleneck and want to make sure that you have O(1) test functions.
  • If you know that the expression you're looking for is anchored, use anchors in your regex. This can help the engine a lot to make your scanners more efficient.
  • In addition to anchors, constant strings at the start or end of a regular expression can help the engine to quickly scan a string. Note that for example "(a-d|aebf)" and "ab(cd|ef)" are equivalent, but only the second form has a constant start the regex engine can recognize.
  • Try to avoid alternations if possible or at least factor them out as in the example above.
  • If neither anchors nor constant strings are in sight, maybe "standalone" (sometimes also called "possessive") regular expressions can be helpful. Try the following:
    (let ((target (make-string 10000 :initial-element #\a))
          (scanner-1 (create-scanner "a*\\d"))
          (scanner-2 (create-scanner "(?>a*)\\d")))
      (time (scan scanner-1 target))
      (time (scan scanner-2 target)))
    
  • Consider using "single-line mode" if it makes sense for your task. By default (following Perl's practice), a dot means to search for any character except line breaks. In single-line mode a dot searches for any character which in some cases means that large parts of the target can actually be skipped. This can be vastly more efficient for large targets.
  • Don't use capturing register groups where a non-capturing group would do, i.e. only use registers if you need to refer to them later. If you use a register, each scan process needs to allocate space for it and update its contents (possibly many times) until it's finished. (In Perl parlance - use "(?:foo)" instead of "(foo)" whenever possible.)
  • In addition to what has been said in the last hint, note that Perl semantics force the regex engine to report the last match for each register. This implies for example that "([a-c])+" and "[a-c]*([a-c])" have exactly the same semantics but completely different performance characteristics. (Actually, in some cases CL-PPCRE automatically converts expressions from the first type into the second type. That's not always possible, though, and you shouldn't rely on it.)
  • By default, repetitions are "greedy" in Perl (and thus in CL-PPCRE). This has an impact on performance and also on the actual outcome of a scan. Look at your repetitions and ponder if a greedy repetition is really what you want.

 

Acknowledgements

Although I didn't use their code, I was heavily inspired by looking at the Scheme/CL regex implementations of Dorai Sitaram and Michael Parker. Also, the nice folks from CMUCL's mailing list as well as the output of Perl's use re "debug" pragma have been very helpful in optimizing the scanners created by CL-PPCRE.

The list of people who participated in this project in one way or the other has grown too long to maintain it here. See the ChangeLog for all the people who helped with patches, bug reports, or in other ways. Thanks to all of them!

Thanks to the guys at "Café Olé" in Hamburg where I wrote most of the 0.1.0 release and thanks to my wife for lending me her PowerBook to test early versions of CL-PPCRE with MCL and OpenMCL.

$Header: /usr/local/cvsrep/cl-ppcre/doc/index.html,v 1.200 2009/10/28 07:36:31 edi Exp $

BACK TO MY HOMEPAGE cl-ppcre-2.0.3/errors.lisp0000644000175700010010000000711611254505513013652 0ustar ediNone;;; -*- Mode: LISP; Syntax: COMMON-LISP; Package: CL-PPCRE; Base: 10 -*- ;;; $Header: /usr/local/cvsrep/cl-ppcre/errors.lisp,v 1.22 2009/09/17 19:17:31 edi Exp $ ;;; Copyright (c) 2002-2009, Dr. Edmund Weitz. All rights reserved. ;;; Redistribution and use in source and binary forms, with or without ;;; modification, are permitted provided that the following conditions ;;; are met: ;;; * Redistributions of source code must retain the above copyright ;;; notice, this list of conditions and the following disclaimer. ;;; * Redistributions in binary form must reproduce the above ;;; copyright notice, this list of conditions and the following ;;; disclaimer in the documentation and/or other materials ;;; provided with the distribution. ;;; THIS SOFTWARE IS PROVIDED BY THE AUTHOR 'AS IS' AND ANY EXPRESSED ;;; OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED ;;; WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ;;; ARE DISCLAIMED. IN NO EVENT SHALL THE AUTHOR BE LIABLE FOR ANY ;;; DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL ;;; DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE ;;; GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS ;;; INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, ;;; WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING ;;; NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE OF THIS ;;; SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. (in-package :cl-ppcre) (defvar *syntax-error-string* nil "The string which caused the syntax error.") (define-condition ppcre-error (simple-error) () (:documentation "All errors signaled by CL-PPCRE are of this type.")) (define-condition ppcre-syntax-error (ppcre-error) ((string :initarg :string :reader ppcre-syntax-error-string) (pos :initarg :pos :reader ppcre-syntax-error-pos)) (:default-initargs :pos nil :string *syntax-error-string*) (:report (lambda (condition stream) (format stream "~?~@[ at position ~A~]~@[ in string ~S~]" (simple-condition-format-control condition) (simple-condition-format-arguments condition) (ppcre-syntax-error-pos condition) (ppcre-syntax-error-string condition)))) (:documentation "Signaled if CL-PPCRE's parser encounters an error when trying to parse a regex string or to convert a parse tree into its internal representation.")) (setf (documentation 'ppcre-syntax-error-string 'function) "Returns the string the parser was parsing when the error was encountered \(or NIL if the error happened while trying to convert a parse tree).") (setf (documentation 'ppcre-syntax-error-pos 'function) "Returns the position within the string where the error occurred \(or NIL if the error happened while trying to convert a parse tree") (define-condition ppcre-invocation-error (ppcre-error) () (:documentation "Signaled when CL-PPCRE functions are invoked with wrong arguments.")) (defmacro signal-syntax-error* (pos format-control &rest format-arguments) `(error 'ppcre-syntax-error :pos ,pos :format-control ,format-control :format-arguments (list ,@format-arguments))) (defmacro signal-syntax-error (format-control &rest format-arguments) `(signal-syntax-error* nil ,format-control ,@format-arguments)) (defmacro signal-invocation-error (format-control &rest format-arguments) `(error 'ppcre-invocation-error :format-control ,format-control :format-arguments (list ,@format-arguments))) cl-ppcre-2.0.3/lexer.lisp0000644000175700010010000010142011254505513013446 0ustar ediNone;;; -*- Mode: LISP; Syntax: COMMON-LISP; Package: CL-PPCRE; Base: 10 -*- ;;; $Header: /usr/local/cvsrep/cl-ppcre/lexer.lisp,v 1.35 2009/09/17 19:17:31 edi Exp $ ;;; The lexer's responsibility is to convert the regex string into a ;;; sequence of tokens which are in turn consumed by the parser. ;;; ;;; The lexer is aware of Perl's 'extended mode' and it also 'knows' ;;; (with a little help from the parser) how many register groups it ;;; has opened so far. (The latter is necessary for interpreting ;;; strings like "\\10" correctly.) ;;; Copyright (c) 2002-2009, Dr. Edmund Weitz. All rights reserved. ;;; Redistribution and use in source and binary forms, with or without ;;; modification, are permitted provided that the following conditions ;;; are met: ;;; * Redistributions of source code must retain the above copyright ;;; notice, this list of conditions and the following disclaimer. ;;; * Redistributions in binary form must reproduce the above ;;; copyright notice, this list of conditions and the following ;;; disclaimer in the documentation and/or other materials ;;; provided with the distribution. ;;; THIS SOFTWARE IS PROVIDED BY THE AUTHOR 'AS IS' AND ANY EXPRESSED ;;; OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED ;;; WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ;;; ARE DISCLAIMED. IN NO EVENT SHALL THE AUTHOR BE LIABLE FOR ANY ;;; DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL ;;; DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE ;;; GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS ;;; INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, ;;; WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING ;;; NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE OF THIS ;;; SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. (in-package :cl-ppcre) (declaim (inline map-char-to-special-class)) (defun map-char-to-special-char-class (chr) (declare #.*standard-optimize-settings*) "Maps escaped characters like \"\\d\" to the tokens which represent their associated character classes." (case chr ((#\d) :digit-class) ((#\D) :non-digit-class) ((#\w) :word-char-class) ((#\W) :non-word-char-class) ((#\s) :whitespace-char-class) ((#\S) :non-whitespace-char-class))) (defstruct (lexer (:constructor make-lexer-internal)) "LEXER structures are used to hold the regex string which is currently lexed and to keep track of the lexer's state." (str "" :type string :read-only t) (len 0 :type fixnum :read-only t) (reg 0 :type fixnum) (pos 0 :type fixnum) (last-pos nil :type list)) (defun make-lexer (string) (declare (inline make-lexer-internal) #-:genera (string string)) (make-lexer-internal :str (maybe-coerce-to-simple-string string) :len (length string))) (declaim (inline end-of-string-p)) (defun end-of-string-p (lexer) (declare #.*standard-optimize-settings*) "Tests whether we're at the end of the regex string." (<= (lexer-len lexer) (lexer-pos lexer))) (declaim (inline looking-at-p)) (defun looking-at-p (lexer chr) (declare #.*standard-optimize-settings*) "Tests whether the next character the lexer would see is CHR. Does not respect extended mode." (and (not (end-of-string-p lexer)) (char= (schar (lexer-str lexer) (lexer-pos lexer)) chr))) (declaim (inline next-char-non-extended)) (defun next-char-non-extended (lexer) (declare #.*standard-optimize-settings*) "Returns the next character which is to be examined and updates the POS slot. Does not respect extended mode." (cond ((end-of-string-p lexer) nil) (t (prog1 (schar (lexer-str lexer) (lexer-pos lexer)) (incf (lexer-pos lexer)))))) (defun next-char (lexer) (declare #.*standard-optimize-settings*) "Returns the next character which is to be examined and updates the POS slot. Respects extended mode, i.e. whitespace, comments, and also nested comments are skipped if applicable." (let ((next-char (next-char-non-extended lexer)) last-loop-pos) (loop ;; remember where we started (setq last-loop-pos (lexer-pos lexer)) ;; first we look for nested comments like (?#foo) (when (and next-char (char= next-char #\() (looking-at-p lexer #\?)) (incf (lexer-pos lexer)) (cond ((looking-at-p lexer #\#) ;; must be a nested comment - so we have to search for ;; the closing parenthesis (let ((error-pos (- (lexer-pos lexer) 2))) (unless ;; loop 'til ')' or end of regex string and ;; return NIL if ')' wasn't encountered (loop for skip-char = next-char then (next-char-non-extended lexer) while (and skip-char (char/= skip-char #\))) finally (return skip-char)) (signal-syntax-error* error-pos "Comment group not closed."))) (setq next-char (next-char-non-extended lexer))) (t ;; undo effect of previous INCF if we didn't see a # (decf (lexer-pos lexer))))) (when *extended-mode-p* ;; now - if we're in extended mode - we skip whitespace and ;; comments; repeat the following loop while we look at ;; whitespace or #\# (loop while (and next-char (or (char= next-char #\#) (whitespacep next-char))) do (setq next-char (if (char= next-char #\#) ;; if we saw a comment marker skip until ;; we're behind #\Newline... (loop for skip-char = next-char then (next-char-non-extended lexer) while (and skip-char (char/= skip-char #\Newline)) finally (return (next-char-non-extended lexer))) ;; ...otherwise (whitespace) skip until we ;; see the next non-whitespace character (loop for skip-char = next-char then (next-char-non-extended lexer) while (and skip-char (whitespacep skip-char)) finally (return skip-char)))))) ;; if the position has moved we have to repeat our tests ;; because of cases like /^a (?#xxx) (?#yyy) {3}c/x which ;; would be equivalent to /^a{3}c/ in Perl (unless (> (lexer-pos lexer) last-loop-pos) (return next-char))))) (declaim (inline fail)) (defun fail (lexer) (declare #.*standard-optimize-settings*) "Moves (LEXER-POS LEXER) back to the last position stored in \(LEXER-LAST-POS LEXER) and pops the LAST-POS stack." (unless (lexer-last-pos lexer) (signal-syntax-error "LAST-POS stack of LEXER ~A is empty." lexer)) (setf (lexer-pos lexer) (pop (lexer-last-pos lexer))) nil) (defun get-number (lexer &key (radix 10) max-length no-whitespace-p) (declare #.*standard-optimize-settings*) "Read and consume the number the lexer is currently looking at and return it. Returns NIL if no number could be identified. RADIX is used as in PARSE-INTEGER. If MAX-LENGTH is not NIL we'll read at most the next MAX-LENGTH characters. If NO-WHITESPACE-P is not NIL we don't tolerate whitespace in front of the number." (when (or (end-of-string-p lexer) (and no-whitespace-p (whitespacep (schar (lexer-str lexer) (lexer-pos lexer))))) (return-from get-number nil)) (multiple-value-bind (integer new-pos) (parse-integer (lexer-str lexer) :start (lexer-pos lexer) :end (if max-length (let ((end-pos (+ (lexer-pos lexer) (the fixnum max-length))) (lexer-len (lexer-len lexer))) (if (< end-pos lexer-len) end-pos lexer-len)) (lexer-len lexer)) :radix radix :junk-allowed t) (cond ((and integer (>= (the fixnum integer) 0)) (setf (lexer-pos lexer) new-pos) integer) (t nil)))) (declaim (inline try-number)) (defun try-number (lexer &key (radix 10) max-length no-whitespace-p) (declare #.*standard-optimize-settings*) "Like GET-NUMBER but won't consume anything if no number is seen." ;; remember current position (push (lexer-pos lexer) (lexer-last-pos lexer)) (let ((number (get-number lexer :radix radix :max-length max-length :no-whitespace-p no-whitespace-p))) (or number (fail lexer)))) (declaim (inline make-char-from-code)) (defun make-char-from-code (number error-pos) (declare #.*standard-optimize-settings*) "Create character from char-code NUMBER. NUMBER can be NIL which is interpreted as 0. ERROR-POS is the position where the corresponding number started within the regex string." ;; only look at rightmost eight bits in compliance with Perl (let ((code (logand #o377 (the fixnum (or number 0))))) (or (and (< code char-code-limit) (code-char code)) (signal-syntax-error* error-pos "No character for hex-code ~X." number)))) (defun unescape-char (lexer) (declare #.*standard-optimize-settings*) "Convert the characters\(s) following a backslash into a token which is returned. This function is to be called when the backslash has already been consumed. Special character classes like \\W are handled elsewhere." (when (end-of-string-p lexer) (signal-syntax-error "String ends with backslash.")) (let ((chr (next-char-non-extended lexer))) (case chr ((#\E) ;; if \Q quoting is on this is ignored, otherwise it's just an ;; #\E (if *allow-quoting* :void #\E)) ((#\c) ;; \cx means control-x in Perl (let ((next-char (next-char-non-extended lexer))) (unless next-char (signal-syntax-error* (lexer-pos lexer) "Character missing after '\\c' at position ~A.")) (code-char (logxor #x40 (char-code (char-upcase next-char)))))) ((#\x) ;; \x should be followed by a hexadecimal char code, ;; two digits or less (let* ((error-pos (lexer-pos lexer)) (number (get-number lexer :radix 16 :max-length 2 :no-whitespace-p t))) ;; note that it is OK if \x is followed by zero digits (make-char-from-code number error-pos))) ((#\0 #\1 #\2 #\3 #\4 #\5 #\6 #\7 #\8 #\9) ;; \x should be followed by an octal char code, ;; three digits or less (let* ((error-pos (decf (lexer-pos lexer))) (number (get-number lexer :radix 8 :max-length 3))) (make-char-from-code number error-pos))) ;; the following five character names are 'semi-standard' ;; according to the CLHS but I'm not aware of any implementation ;; that doesn't implement them ((#\t) #\Tab) ((#\n) #\Newline) ((#\r) #\Return) ((#\f) #\Page) ((#\b) #\Backspace) ((#\a) (code-char 7)) ; ASCII bell ((#\e) (code-char 27)) ; ASCII escape (otherwise ;; all other characters aren't affected by a backslash chr)))) (defun read-char-property (lexer first-char) (declare #.*standard-optimize-settings*) (unless (eql (next-char-non-extended lexer) #\{) (signal-syntax-error* (lexer-pos lexer) "Expected left brace after \\~A." first-char)) (let ((name (with-output-to-string (out nil :element-type #+:lispworks 'lw:simple-char #-:lispworks 'character) (loop (let ((char (or (next-char-non-extended lexer) (signal-syntax-error "Unexpected EOF after \\~A{." first-char)))) (when (char= char #\}) (return)) (write-char char out)))))) (list (if (char= first-char #\p) :property :inverted-property) ;; we must reverse here because of what PARSE-STRING does (nreverse name)))) (defun collect-char-class (lexer) "Reads and consumes characters from regex string until a right bracket is seen. Assembles them into a list \(which is returned) of characters, character ranges, like \(:RANGE #\\A #\\E) for a-e, and tokens representing special character classes." (declare #.*standard-optimize-settings*) (let ((start-pos (lexer-pos lexer)) ; remember start for error message hyphen-seen last-char list) (flet ((handle-char (c) "Do the right thing with character C depending on whether we're inside a range or not." (cond ((and hyphen-seen last-char) (setf (car list) (list :range last-char c) last-char nil)) (t (push c list) (setq last-char c))) (setq hyphen-seen nil))) (loop for first = t then nil for c = (next-char-non-extended lexer) ;; leave loop if at end of string while c do (cond ((char= c #\\) ;; we've seen a backslash (let ((next-char (next-char-non-extended lexer))) (case next-char ((#\d #\D #\w #\W #\s #\S) ;; a special character class (push (map-char-to-special-char-class next-char) list) ;; if the last character was a hyphen ;; just collect it literally (when hyphen-seen (push #\- list)) ;; if the next character is a hyphen do the same (when (looking-at-p lexer #\-) (push #\- list) (incf (lexer-pos lexer))) (setq hyphen-seen nil)) ((#\P #\p) ;; maybe a character property (cond ((null *property-resolver*) (handle-char next-char)) (t (push (read-char-property lexer next-char) list) ;; if the last character was a hyphen ;; just collect it literally (when hyphen-seen (push #\- list)) ;; if the next character is a hyphen do the same (when (looking-at-p lexer #\-) (push #\- list) (incf (lexer-pos lexer))) (setq hyphen-seen nil)))) ((#\E) ;; if \Q quoting is on we ignore \E, ;; otherwise it's just a plain #\E (unless *allow-quoting* (handle-char #\E))) (otherwise ;; otherwise unescape the following character(s) (decf (lexer-pos lexer)) (handle-char (unescape-char lexer)))))) (first ;; the first character must not be a right bracket ;; and isn't treated specially if it's a hyphen (handle-char c)) ((char= c #\]) ;; end of character class ;; make sure we collect a pending hyphen (when hyphen-seen (setq hyphen-seen nil) (handle-char #\-)) ;; reverse the list to preserve the order intended ;; by the author of the regex string (return-from collect-char-class (nreverse list))) ((and (char= c #\-) last-char (not hyphen-seen)) ;; if the last character was 'just a character' ;; we expect to be in the middle of a range (setq hyphen-seen t)) ((char= c #\-) ;; otherwise this is just an ordinary hyphen (handle-char #\-)) (t ;; default case - just collect the character (handle-char c)))) ;; we can only exit the loop normally if we've reached the end ;; of the regex string without seeing a right bracket (signal-syntax-error* start-pos "Missing right bracket to close character class.")))) (defun maybe-parse-flags (lexer) (declare #.*standard-optimize-settings*) "Reads a sequence of modifiers \(including #\\- to reverse their meaning) and returns a corresponding list of \"flag\" tokens. The \"x\" modifier is treated specially in that it dynamically modifies the behaviour of the lexer itself via the special variable *EXTENDED-MODE-P*." (prog1 (loop with set = t for chr = (next-char-non-extended lexer) unless chr do (signal-syntax-error "Unexpected end of string.") while (find chr "-imsx" :test #'char=) ;; the first #\- will invert the meaning of all modifiers ;; following it if (char= chr #\-) do (setq set nil) else if (char= chr #\x) do (setq *extended-mode-p* set) else collect (if set (case chr ((#\i) :case-insensitive-p) ((#\m) :multi-line-mode-p) ((#\s) :single-line-mode-p)) (case chr ((#\i) :case-sensitive-p) ((#\m) :not-multi-line-mode-p) ((#\s) :not-single-line-mode-p)))) (decf (lexer-pos lexer)))) (defun get-quantifier (lexer) (declare #.*standard-optimize-settings*) "Returns a list of two values (min max) if what the lexer is looking at can be interpreted as a quantifier. Otherwise returns NIL and resets the lexer to its old position." ;; remember starting position for FAIL and UNGET-TOKEN functions (push (lexer-pos lexer) (lexer-last-pos lexer)) (let ((next-char (next-char lexer))) (case next-char ((#\*) ;; * (Kleene star): match 0 or more times '(0 nil)) ((#\+) ;; +: match 1 or more times '(1 nil)) ((#\?) ;; ?: match 0 or 1 times '(0 1)) ((#\{) ;; one of ;; {n}: match exactly n times ;; {n,}: match at least n times ;; {n,m}: match at least n but not more than m times ;; note that anything not matching one of these patterns will ;; be interpreted literally - even whitespace isn't allowed (let ((num1 (get-number lexer :no-whitespace-p t))) (if num1 (let ((next-char (next-char-non-extended lexer))) (case next-char ((#\,) (let* ((num2 (get-number lexer :no-whitespace-p t)) (next-char (next-char-non-extended lexer))) (case next-char ((#\}) ;; this is the case {n,} (NUM2 is NIL) or {n,m} (list num1 num2)) (otherwise (fail lexer))))) ((#\}) ;; this is the case {n} (list num1 num1)) (otherwise (fail lexer)))) ;; no number following left curly brace, so we treat it ;; like a normal character (fail lexer)))) ;; cannot be a quantifier (otherwise (fail lexer))))) (defun parse-register-name-aux (lexer) "Reads and returns the name in a named register group. It is assumed that the starting #\< character has already been read. The closing #\> will also be consumed." ;; we have to look for an ending > character now (let ((end-name (position #\> (lexer-str lexer) :start (lexer-pos lexer) :test #'char=))) (unless end-name ;; there has to be > somewhere, syntax error otherwise (signal-syntax-error* (1- (lexer-pos lexer)) "Opening #\< in named group has no closing #\>.")) (let ((name (subseq (lexer-str lexer) (lexer-pos lexer) end-name))) (unless (every #'(lambda (char) (or (alphanumericp char) (char= #\- char))) name) ;; register name can contain only alphanumeric characters or #\- (signal-syntax-error* (lexer-pos lexer) "Invalid character in named register group.")) ;; advance lexer beyond "" part (setf (lexer-pos lexer) (1+ end-name)) name))) (defun get-token (lexer) (declare #.*standard-optimize-settings*) "Returns and consumes the next token from the regex string \(or NIL)." ;; remember starting position for UNGET-TOKEN function (push (lexer-pos lexer) (lexer-last-pos lexer)) (let ((next-char (next-char lexer))) (cond (next-char (case next-char ;; the easy cases first - the following six characters ;; always have a special meaning and get translated ;; into tokens immediately ((#\)) :close-paren) ((#\|) :vertical-bar) ((#\?) :question-mark) ((#\.) :everything) ((#\^) :start-anchor) ((#\$) :end-anchor) ((#\+ #\*) ;; quantifiers will always be consumend by ;; GET-QUANTIFIER, they must not appear here (signal-syntax-error* (1- (lexer-pos lexer)) "Quantifier '~A' not allowed." next-char)) ((#\{) ;; left brace isn't a special character in it's own ;; right but we must check if what follows might ;; look like a quantifier (let ((this-pos (lexer-pos lexer)) (this-last-pos (lexer-last-pos lexer))) (unget-token lexer) (when (get-quantifier lexer) (signal-syntax-error* (car this-last-pos) "Quantifier '~A' not allowed." (subseq (lexer-str lexer) (car this-last-pos) (lexer-pos lexer)))) (setf (lexer-pos lexer) this-pos (lexer-last-pos lexer) this-last-pos) next-char)) ((#\[) ;; left bracket always starts a character class (cons (cond ((looking-at-p lexer #\^) (incf (lexer-pos lexer)) :inverted-char-class) (t :char-class)) (collect-char-class lexer))) ((#\\) ;; backslash might mean different things so we have ;; to peek one char ahead: (let ((next-char (next-char-non-extended lexer))) (case next-char ((#\A) :modeless-start-anchor) ((#\Z) :modeless-end-anchor) ((#\z) :modeless-end-anchor-no-newline) ((#\b) :word-boundary) ((#\B) :non-word-boundary) ((#\k) (cond ((and *allow-named-registers* (looking-at-p lexer #\<)) ;; back-referencing a named register (incf (lexer-pos lexer)) (list :back-reference (nreverse (parse-register-name-aux lexer)))) (t ;; false alarm, just unescape \k #\k))) ((#\d #\D #\w #\W #\s #\S) ;; these will be treated like character classes (map-char-to-special-char-class next-char)) ((#\1 #\2 #\3 #\4 #\5 #\6 #\7 #\8 #\9) ;; uh, a digit... (let* ((old-pos (decf (lexer-pos lexer))) ;; ...so let's get the whole number first (backref-number (get-number lexer))) (declare (fixnum backref-number)) (cond ((and (> backref-number (lexer-reg lexer)) (<= 10 backref-number)) ;; \10 and higher are treated as octal ;; character codes if we haven't ;; opened that much register groups ;; yet (setf (lexer-pos lexer) old-pos) ;; re-read the number from the old ;; position and convert it to its ;; corresponding character (make-char-from-code (get-number lexer :radix 8 :max-length 3) old-pos)) (t ;; otherwise this must refer to a ;; backreference (list :back-reference backref-number))))) ((#\0) ;; this always means an octal character code ;; (at most three digits) (let ((old-pos (decf (lexer-pos lexer)))) (make-char-from-code (get-number lexer :radix 8 :max-length 3) old-pos))) ((#\P #\p) ;; might be a named property (cond (*property-resolver* (read-char-property lexer next-char)) (t next-char))) (otherwise ;; in all other cases just unescape the ;; character (decf (lexer-pos lexer)) (unescape-char lexer))))) ((#\() ;; an open parenthesis might mean different things ;; depending on what follows... (cond ((looking-at-p lexer #\?) ;; this is the case '(?' (and probably more behind) (incf (lexer-pos lexer)) ;; we have to check for modifiers first ;; because a colon might follow (let* ((flags (maybe-parse-flags lexer)) (next-char (next-char-non-extended lexer))) ;; modifiers are only allowed if a colon ;; or a closing parenthesis are following (when (and flags (not (find next-char ":)" :test #'char=))) (signal-syntax-error* (car (lexer-last-pos lexer)) "Sequence '~A' not recognized." (subseq (lexer-str lexer) (car (lexer-last-pos lexer)) (lexer-pos lexer)))) (case next-char ((nil) ;; syntax error (signal-syntax-error "End of string following '(?'.")) ((#\)) ;; an empty group except for the flags ;; (if there are any) (or (and flags (cons :flags flags)) :void)) ((#\() ;; branch :open-paren-paren) ((#\>) ;; standalone :open-paren-greater) ((#\=) ;; positive look-ahead :open-paren-equal) ((#\!) ;; negative look-ahead :open-paren-exclamation) ((#\:) ;; non-capturing group - return flags as ;; second value (values :open-paren-colon flags)) ((#\<) ;; might be a look-behind assertion or a named group, so ;; check next character (let ((next-char (next-char-non-extended lexer))) (if (alpha-char-p next-char) (progn ;; we have encountered a named group ;; are we supporting register naming? (unless *allow-named-registers* (signal-syntax-error* (1- (lexer-pos lexer)) "Character '~A' may not follow '(?<'." next-char)) ;; put the letter back (decf (lexer-pos lexer)) ;; named group :open-paren-less-letter) (case next-char ((#\=) ;; positive look-behind :open-paren-less-equal) ((#\!) ;; negative look-behind :open-paren-less-exclamation) ((#\)) ;; Perl allows "(?<)" and treats ;; it like a null string :void) ((nil) ;; syntax error (signal-syntax-error "End of string following '(?<'.")) (t ;; also syntax error (signal-syntax-error* (1- (lexer-pos lexer)) "Character '~A' may not follow '(?<'." next-char )))))) (otherwise (signal-syntax-error* (1- (lexer-pos lexer)) "Character '~A' may not follow '(?'." next-char))))) (t ;; if next-char was not #\? (this is within ;; the first COND), we've just seen an opening ;; parenthesis and leave it like that :open-paren))) (otherwise ;; all other characters are their own tokens next-char))) ;; we didn't get a character (this if the "else" branch from ;; the first IF), so we don't return a token but NIL (t (pop (lexer-last-pos lexer)) nil)))) (declaim (inline unget-token)) (defun unget-token (lexer) (declare #.*standard-optimize-settings*) "Moves the lexer back to the last position stored in the LAST-POS stack." (if (lexer-last-pos lexer) (setf (lexer-pos lexer) (pop (lexer-last-pos lexer))) (error "No token to unget \(this should not happen)"))) (declaim (inline start-of-subexpr-p)) (defun start-of-subexpr-p (lexer) (declare #.*standard-optimize-settings*) "Tests whether the next token can start a valid sub-expression, i.e. a stand-alone regex." (let* ((pos (lexer-pos lexer)) (next-char (next-char lexer))) (not (or (null next-char) (prog1 (member (the character next-char) '(#\) #\|) :test #'char=) (setf (lexer-pos lexer) pos)))))) cl-ppcre-2.0.3/optimize.lisp0000644000175700010010000006126011254505513014176 0ustar ediNone;;; -*- Mode: LISP; Syntax: COMMON-LISP; Package: CL-PPCRE; Base: 10 -*- ;;; $Header: /usr/local/cvsrep/cl-ppcre/optimize.lisp,v 1.36 2009/09/17 19:17:31 edi Exp $ ;;; This file contains optimizations which can be applied to converted ;;; parse trees. ;;; Copyright (c) 2002-2009, Dr. Edmund Weitz. All rights reserved. ;;; Redistribution and use in source and binary forms, with or without ;;; modification, are permitted provided that the following conditions ;;; are met: ;;; * Redistributions of source code must retain the above copyright ;;; notice, this list of conditions and the following disclaimer. ;;; * Redistributions in binary form must reproduce the above ;;; copyright notice, this list of conditions and the following ;;; disclaimer in the documentation and/or other materials ;;; provided with the distribution. ;;; THIS SOFTWARE IS PROVIDED BY THE AUTHOR 'AS IS' AND ANY EXPRESSED ;;; OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED ;;; WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ;;; ARE DISCLAIMED. IN NO EVENT SHALL THE AUTHOR BE LIABLE FOR ANY ;;; DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL ;;; DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE ;;; GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS ;;; INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, ;;; WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING ;;; NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE OF THIS ;;; SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. (in-package :cl-ppcre) (defgeneric flatten (regex) (declare #.*standard-optimize-settings*) (:documentation "Merges adjacent sequences and alternations, i.e. it transforms # # #>> to # # #>. This is a destructive operation on REGEX.")) (defmethod flatten ((seq seq)) (declare #.*standard-optimize-settings*) ;; this looks more complicated than it is because we modify SEQ in ;; place to avoid unnecessary consing (let ((elements-rest (elements seq))) (loop (unless elements-rest (return)) (let ((flattened-element (flatten (car elements-rest))) (next-elements-rest (cdr elements-rest))) (cond ((typep flattened-element 'seq) ;; FLATTENED-ELEMENT is a SEQ object, so we "splice" ;; it into out list of elements (let ((flattened-element-elements (elements flattened-element))) (setf (car elements-rest) (car flattened-element-elements) (cdr elements-rest) (nconc (cdr flattened-element-elements) (cdr elements-rest))))) (t ;; otherwise we just replace the current element with ;; its flattened counterpart (setf (car elements-rest) flattened-element))) (setq elements-rest next-elements-rest)))) (let ((elements (elements seq))) (cond ((cadr elements) seq) ((cdr elements) (first elements)) (t (make-instance 'void))))) (defmethod flatten ((alternation alternation)) (declare #.*standard-optimize-settings*) ;; same algorithm as above (let ((choices-rest (choices alternation))) (loop (unless choices-rest (return)) (let ((flattened-choice (flatten (car choices-rest))) (next-choices-rest (cdr choices-rest))) (cond ((typep flattened-choice 'alternation) (let ((flattened-choice-choices (choices flattened-choice))) (setf (car choices-rest) (car flattened-choice-choices) (cdr choices-rest) (nconc (cdr flattened-choice-choices) (cdr choices-rest))))) (t (setf (car choices-rest) flattened-choice))) (setq choices-rest next-choices-rest)))) (let ((choices (choices alternation))) (cond ((cadr choices) alternation) ((cdr choices) (first choices)) (t (signal-syntax-error "Encountered alternation without choices."))))) (defmethod flatten ((branch branch)) (declare #.*standard-optimize-settings*) (with-slots (test then-regex else-regex) branch (setq test (if (numberp test) test (flatten test)) then-regex (flatten then-regex) else-regex (flatten else-regex)) branch)) (defmethod flatten ((regex regex)) (declare #.*standard-optimize-settings*) (typecase regex ((or repetition register lookahead lookbehind standalone) ;; if REGEX contains exactly one inner REGEX object flatten it (setf (regex regex) (flatten (regex regex))) regex) (t ;; otherwise (ANCHOR, BACK-REFERENCE, CHAR-CLASS, EVERYTHING, ;; LOOKAHEAD, LOOKBEHIND, STR, VOID, FILTER, and WORD-BOUNDARY) ;; do nothing regex))) (defgeneric gather-strings (regex) (declare #.*standard-optimize-settings*) (:documentation "Collects adjacent strings or characters into one string provided they have the same case mode. This is a destructive operation on REGEX.")) (defmethod gather-strings ((seq seq)) (declare #.*standard-optimize-settings*) ;; note that GATHER-STRINGS is to be applied after FLATTEN, i.e. it ;; expects SEQ to be flattened already; in particular, SEQ cannot be ;; empty and cannot contain embedded SEQ objects (let* ((start-point (cons nil (elements seq))) (curr-point start-point) old-case-mode collector collector-start (collector-length 0) skip) (declare (fixnum collector-length)) (loop (let ((elements-rest (cdr curr-point))) (unless elements-rest (return)) (let* ((element (car elements-rest)) (case-mode (case-mode element old-case-mode))) (cond ((and case-mode (eq case-mode old-case-mode)) ;; if ELEMENT is a STR and we have collected a STR of ;; the same case mode in the last iteration we ;; concatenate ELEMENT onto COLLECTOR and remember the ;; value of its SKIP slot (let ((old-collector-length collector-length)) (unless (and (adjustable-array-p collector) (array-has-fill-pointer-p collector)) (setq collector (make-array collector-length :initial-contents collector :element-type 'character :fill-pointer t :adjustable t) collector-start nil)) (adjust-array collector (incf collector-length (len element)) :fill-pointer t) (setf (subseq collector old-collector-length) (str element) ;; it suffices to remember the last SKIP slot ;; because due to the way MAYBE-ACCUMULATE ;; works adjacent STR objects have the same ;; SKIP value skip (skip element))) (setf (cdr curr-point) (cdr elements-rest))) (t (let ((collected-string (cond (collector-start collector-start) (collector ;; if we have collected something already ;; we convert it into a STR (make-instance 'str :skip skip :str collector :case-insensitive-p (eq old-case-mode :case-insensitive))) (t nil)))) (cond (case-mode ;; if ELEMENT is a string with a different case ;; mode than the last one we have either just ;; converted COLLECTOR into a STR or COLLECTOR ;; is still empty; in both cases we can now ;; begin to fill it anew (setq collector (str element) collector-start element ;; and we remember the SKIP value as above skip (skip element) collector-length (len element)) (cond (collected-string (setf (car elements-rest) collected-string curr-point (cdr curr-point))) (t (setf (cdr curr-point) (cdr elements-rest))))) (t ;; otherwise this is not a STR so we apply ;; GATHER-STRINGS to it and collect it directly ;; into RESULT (cond (collected-string (setf (car elements-rest) collected-string curr-point (cdr curr-point) (cdr curr-point) (cons (gather-strings element) (cdr curr-point)) curr-point (cdr curr-point))) (t (setf (car elements-rest) (gather-strings element) curr-point (cdr curr-point)))) ;; we also have to empty COLLECTOR here in case ;; it was still filled from the last iteration (setq collector nil collector-start nil)))))) (setq old-case-mode case-mode)))) (when collector (setf (cdr curr-point) (cons (make-instance 'str :skip skip :str collector :case-insensitive-p (eq old-case-mode :case-insensitive)) nil))) (setf (elements seq) (cdr start-point)) seq)) (defmethod gather-strings ((alternation alternation)) (declare #.*standard-optimize-settings*) ;; loop ON the choices of ALTERNATION so we can modify them directly (loop for choices-rest on (choices alternation) while choices-rest do (setf (car choices-rest) (gather-strings (car choices-rest)))) alternation) (defmethod gather-strings ((branch branch)) (declare #.*standard-optimize-settings*) (with-slots (test then-regex else-regex) branch (setq test (if (numberp test) test (gather-strings test)) then-regex (gather-strings then-regex) else-regex (gather-strings else-regex)) branch)) (defmethod gather-strings ((regex regex)) (declare #.*standard-optimize-settings*) (typecase regex ((or repetition register lookahead lookbehind standalone) ;; if REGEX contains exactly one inner REGEX object apply ;; GATHER-STRINGS to it (setf (regex regex) (gather-strings (regex regex))) regex) (t ;; otherwise (ANCHOR, BACK-REFERENCE, CHAR-CLASS, EVERYTHING, ;; LOOKAHEAD, LOOKBEHIND, STR, VOID, FILTER, and WORD-BOUNDARY) ;; do nothing regex))) ;; Note that START-ANCHORED-P will be called after FLATTEN and GATHER-STRINGS. (defgeneric start-anchored-p (regex &optional in-seq-p) (declare #.*standard-optimize-settings*) (:documentation "Returns T if REGEX starts with a \"real\" start anchor, i.e. one that's not in multi-line mode, NIL otherwise. If IN-SEQ-P is true the function will return :ZERO-LENGTH if REGEX is a zero-length assertion.")) (defmethod start-anchored-p ((seq seq) &optional in-seq-p) (declare (ignore in-seq-p)) ;; note that START-ANCHORED-P is to be applied after FLATTEN and ;; GATHER-STRINGS, i.e. SEQ cannot be empty and cannot contain ;; embedded SEQ objects (loop for element in (elements seq) for anchored-p = (start-anchored-p element t) ;; skip zero-length elements because they won't affect the ;; "anchoredness" of the sequence while (eq anchored-p :zero-length) finally (return (and anchored-p (not (eq anchored-p :zero-length)))))) (defmethod start-anchored-p ((alternation alternation) &optional in-seq-p) (declare #.*standard-optimize-settings*) (declare (ignore in-seq-p)) ;; clearly an alternation can only be start-anchored if all of its ;; choices are start-anchored (loop for choice in (choices alternation) always (start-anchored-p choice))) (defmethod start-anchored-p ((branch branch) &optional in-seq-p) (declare #.*standard-optimize-settings*) (declare (ignore in-seq-p)) (and (start-anchored-p (then-regex branch)) (start-anchored-p (else-regex branch)))) (defmethod start-anchored-p ((repetition repetition) &optional in-seq-p) (declare #.*standard-optimize-settings*) (declare (ignore in-seq-p)) ;; well, this wouldn't make much sense, but anyway... (and (plusp (minimum repetition)) (start-anchored-p (regex repetition)))) (defmethod start-anchored-p ((register register) &optional in-seq-p) (declare #.*standard-optimize-settings*) (declare (ignore in-seq-p)) (start-anchored-p (regex register))) (defmethod start-anchored-p ((standalone standalone) &optional in-seq-p) (declare #.*standard-optimize-settings*) (declare (ignore in-seq-p)) (start-anchored-p (regex standalone))) (defmethod start-anchored-p ((anchor anchor) &optional in-seq-p) (declare #.*standard-optimize-settings*) (declare (ignore in-seq-p)) (and (startp anchor) (not (multi-line-p anchor)))) (defmethod start-anchored-p ((regex regex) &optional in-seq-p) (declare #.*standard-optimize-settings*) (typecase regex ((or lookahead lookbehind word-boundary void) ;; zero-length assertions (if in-seq-p :zero-length nil)) (filter (if (and in-seq-p (len regex) (zerop (len regex))) :zero-length nil)) (t ;; BACK-REFERENCE, CHAR-CLASS, EVERYTHING, and STR nil))) ;; Note that END-STRING-AUX will be called after FLATTEN and GATHER-STRINGS. (defgeneric end-string-aux (regex &optional old-case-insensitive-p) (declare #.*standard-optimize-settings*) (:documentation "Returns the constant string (if it exists) REGEX ends with wrapped into a STR object, otherwise NIL. OLD-CASE-INSENSITIVE-P is the CASE-INSENSITIVE-P slot of the last STR collected or :VOID if no STR has been collected yet. (This is a helper function called by END-STRIN.)")) (defmethod end-string-aux ((str str) &optional (old-case-insensitive-p :void)) (declare #.*standard-optimize-settings*) (declare (special last-str)) (cond ((and (not (skip str)) ; avoid constituents of STARTS-WITH ;; only use STR if nothing has been collected yet or if ;; the collected string has the same value for ;; CASE-INSENSITIVE-P (or (eq old-case-insensitive-p :void) (eq (case-insensitive-p str) old-case-insensitive-p))) (setf last-str str ;; set the SKIP property of this STR (skip str) t) str) (t nil))) (defmethod end-string-aux ((seq seq) &optional (old-case-insensitive-p :void)) (declare #.*standard-optimize-settings*) (declare (special continuep)) (let (case-insensitive-p concatenated-string concatenated-start (concatenated-length 0)) (declare (fixnum concatenated-length)) (loop for element in (reverse (elements seq)) ;; remember the case-(in)sensitivity of the last relevant ;; STR object for loop-old-case-insensitive-p = old-case-insensitive-p then (if skip loop-old-case-insensitive-p (case-insensitive-p element-end)) ;; the end-string of the current element for element-end = (end-string-aux element loop-old-case-insensitive-p) ;; whether we encountered a zero-length element for skip = (if element-end (zerop (len element-end)) nil) ;; set CONTINUEP to NIL if we have to stop collecting to ;; alert END-STRING-AUX methods on enclosing SEQ objects unless element-end do (setq continuep nil) ;; end loop if we neither got a STR nor a zero-length ;; element while element-end ;; only collect if not zero-length unless skip do (cond (concatenated-string (when concatenated-start (setf concatenated-string (make-array concatenated-length :initial-contents (reverse (str concatenated-start)) :element-type 'character :fill-pointer t :adjustable t) concatenated-start nil)) (let ((len (len element-end)) (str (str element-end))) (declare (fixnum len)) (incf concatenated-length len) (loop for i of-type fixnum downfrom (1- len) to 0 do (vector-push-extend (char str i) concatenated-string)))) (t (setf concatenated-string t concatenated-start element-end concatenated-length (len element-end) case-insensitive-p (case-insensitive-p element-end)))) ;; stop collecting if END-STRING-AUX on inner SEQ has said so while continuep) (cond ((zerop concatenated-length) ;; don't bother to return zero-length strings nil) (concatenated-start concatenated-start) (t (make-instance 'str :str (nreverse concatenated-string) :case-insensitive-p case-insensitive-p))))) (defmethod end-string-aux ((register register) &optional (old-case-insensitive-p :void)) (declare #.*standard-optimize-settings*) (end-string-aux (regex register) old-case-insensitive-p)) (defmethod end-string-aux ((standalone standalone) &optional (old-case-insensitive-p :void)) (declare #.*standard-optimize-settings*) (end-string-aux (regex standalone) old-case-insensitive-p)) (defmethod end-string-aux ((regex regex) &optional (old-case-insensitive-p :void)) (declare #.*standard-optimize-settings*) (declare (special last-str end-anchored-p continuep)) (typecase regex ((or anchor lookahead lookbehind word-boundary void) ;; a zero-length REGEX object - for the sake of END-STRING-AUX ;; this is a zero-length string (when (and (typep regex 'anchor) (not (startp regex)) (or (no-newline-p regex) (not (multi-line-p regex))) (eq old-case-insensitive-p :void)) ;; if this is a "real" end-anchor and we haven't collected ;; anything so far we can set END-ANCHORED-P (where 1 or 0 ;; indicate whether we accept a #\Newline at the end or not) (setq end-anchored-p (if (no-newline-p regex) 0 1))) (make-instance 'str :str "" :case-insensitive-p :void)) (t ;; (ALTERNATION, BACK-REFERENCE, BRANCH, CHAR-CLASS, EVERYTHING, ;; REPETITION, FILTER) nil))) (defun end-string (regex) (declare (special end-string-offset)) (declare #.*standard-optimize-settings*) "Returns the constant string (if it exists) REGEX ends with wrapped into a STR object, otherwise NIL." ;; LAST-STR points to the last STR object (seen from the end) that's ;; part of END-STRING; CONTINUEP is set to T if we stop collecting ;; in the middle of a SEQ (let ((continuep t) last-str) (declare (special continuep last-str)) (prog1 (end-string-aux regex) (when last-str ;; if we've found something set the START-OF-END-STRING-P of ;; the leftmost STR collected accordingly and remember the ;; OFFSET of this STR (in a special variable provided by the ;; caller of this function) (setf (start-of-end-string-p last-str) t end-string-offset (offset last-str)))))) (defgeneric compute-min-rest (regex current-min-rest) (declare #.*standard-optimize-settings*) (:documentation "Returns the minimal length of REGEX plus CURRENT-MIN-REST. This is similar to REGEX-MIN-LENGTH except that it recurses down into REGEX and sets the MIN-REST slots of REPETITION objects.")) (defmethod compute-min-rest ((seq seq) current-min-rest) (declare #.*standard-optimize-settings*) (loop for element in (reverse (elements seq)) for last-min-rest = current-min-rest then this-min-rest for this-min-rest = (compute-min-rest element last-min-rest) finally (return this-min-rest))) (defmethod compute-min-rest ((alternation alternation) current-min-rest) (declare #.*standard-optimize-settings*) (loop for choice in (choices alternation) minimize (compute-min-rest choice current-min-rest))) (defmethod compute-min-rest ((branch branch) current-min-rest) (declare #.*standard-optimize-settings*) (min (compute-min-rest (then-regex branch) current-min-rest) (compute-min-rest (else-regex branch) current-min-rest))) (defmethod compute-min-rest ((str str) current-min-rest) (declare #.*standard-optimize-settings*) (+ current-min-rest (len str))) (defmethod compute-min-rest ((filter filter) current-min-rest) (declare #.*standard-optimize-settings*) (+ current-min-rest (or (len filter) 0))) (defmethod compute-min-rest ((repetition repetition) current-min-rest) (declare #.*standard-optimize-settings*) (setf (min-rest repetition) current-min-rest) (compute-min-rest (regex repetition) current-min-rest) (+ current-min-rest (* (minimum repetition) (min-len repetition)))) (defmethod compute-min-rest ((register register) current-min-rest) (declare #.*standard-optimize-settings*) (compute-min-rest (regex register) current-min-rest)) (defmethod compute-min-rest ((standalone standalone) current-min-rest) (declare #.*standard-optimize-settings*) (declare (ignore current-min-rest)) (compute-min-rest (regex standalone) 0)) (defmethod compute-min-rest ((lookahead lookahead) current-min-rest) (declare #.*standard-optimize-settings*) (compute-min-rest (regex lookahead) 0) current-min-rest) (defmethod compute-min-rest ((lookbehind lookbehind) current-min-rest) (declare #.*standard-optimize-settings*) (compute-min-rest (regex lookbehind) (+ current-min-rest (len lookbehind))) current-min-rest) (defmethod compute-min-rest ((regex regex) current-min-rest) (declare #.*standard-optimize-settings*) (typecase regex ((or char-class everything) (1+ current-min-rest)) (t ;; zero min-len and no embedded regexes (ANCHOR, ;; BACK-REFERENCE, VOID, and WORD-BOUNDARY) current-min-rest))) cl-ppcre-2.0.3/packages.lisp0000644000175700010010000000520511254505513014111 0ustar ediNone;;; -*- Mode: LISP; Syntax: COMMON-LISP; Package: CL-USER; Base: 10 -*- ;;; $Header: /usr/local/cvsrep/cl-ppcre/packages.lisp,v 1.39 2009/09/17 19:17:31 edi Exp $ ;;; Copyright (c) 2002-2009, Dr. Edmund Weitz. All rights reserved. ;;; Redistribution and use in source and binary forms, with or without ;;; modification, are permitted provided that the following conditions ;;; are met: ;;; * Redistributions of source code must retain the above copyright ;;; notice, this list of conditions and the following disclaimer. ;;; * Redistributions in binary form must reproduce the above ;;; copyright notice, this list of conditions and the following ;;; disclaimer in the documentation and/or other materials ;;; provided with the distribution. ;;; THIS SOFTWARE IS PROVIDED BY THE AUTHOR 'AS IS' AND ANY EXPRESSED ;;; OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED ;;; WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ;;; ARE DISCLAIMED. IN NO EVENT SHALL THE AUTHOR BE LIABLE FOR ANY ;;; DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL ;;; DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE ;;; GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS ;;; INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, ;;; WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING ;;; NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE OF THIS ;;; SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. (in-package :cl-user) (defpackage :cl-ppcre (:nicknames :ppcre) #+:genera (:shadowing-import-from :common-lisp :lambda :simple-string :string) (:use #-:genera :cl #+:genera :future-common-lisp) (:shadow :digit-char-p :defconstant) (:export :parse-string :create-scanner :create-optimized-test-function :parse-tree-synonym :define-parse-tree-synonym :scan :scan-to-strings :do-scans :do-matches :do-matches-as-strings :all-matches :all-matches-as-strings :split :regex-replace :regex-replace-all :regex-apropos :regex-apropos-list :quote-meta-chars :*regex-char-code-limit* :*use-bmh-matchers* :*allow-quoting* :*allow-named-registers* :*optimize-char-classes* :*property-resolver* :ppcre-error :ppcre-invocation-error :ppcre-syntax-error :ppcre-syntax-error-string :ppcre-syntax-error-pos :register-groups-bind :do-register-groups)) cl-ppcre-2.0.3/parser.lisp0000644000175700010010000003640511254505513013635 0ustar ediNone;;; -*- Mode: LISP; Syntax: COMMON-LISP; Package: CL-PPCRE; Base: 10 -*- ;;; $Header: /usr/local/cvsrep/cl-ppcre/parser.lisp,v 1.31 2009/09/17 19:17:31 edi Exp $ ;;; The parser will - with the help of the lexer - parse a regex ;;; string and convert it into a "parse tree" (see docs for details ;;; about the syntax of these trees). Note that the lexer might ;;; return illegal parse trees. It is assumed that the conversion ;;; process later on will track them down. ;;; Copyright (c) 2002-2009, Dr. Edmund Weitz. All rights reserved. ;;; Redistribution and use in source and binary forms, with or without ;;; modification, are permitted provided that the following conditions ;;; are met: ;;; * Redistributions of source code must retain the above copyright ;;; notice, this list of conditions and the following disclaimer. ;;; * Redistributions in binary form must reproduce the above ;;; copyright notice, this list of conditions and the following ;;; disclaimer in the documentation and/or other materials ;;; provided with the distribution. ;;; THIS SOFTWARE IS PROVIDED BY THE AUTHOR 'AS IS' AND ANY EXPRESSED ;;; OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED ;;; WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ;;; ARE DISCLAIMED. IN NO EVENT SHALL THE AUTHOR BE LIABLE FOR ANY ;;; DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL ;;; DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE ;;; GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS ;;; INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, ;;; WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING ;;; NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE OF THIS ;;; SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. (in-package :cl-ppcre) (defun group (lexer) "Parses and consumes a . The productions are: -> \"\(\"\")\" \"\(?:\"\")\" \"\(?>\"\")\" \"\(?:\"\")\" \"\(?=\"\")\" \"\(?!\"\")\" \"\(?<=\"\")\" \"\(?\")\" \"\(?\(\"\")\"\")\" \"\(?\(\"\")\"\")\" \"\(?\"\")\" \(when *ALLOW-NAMED-REGISTERS* is T) where is parsed by the lexer function MAYBE-PARSE-FLAGS. Will return or \( ) where is one of six keywords - see source for details." (declare #.*standard-optimize-settings*) (multiple-value-bind (open-token flags) (get-token lexer) (cond ((eq open-token :open-paren-paren) ;; special case for conditional regular expressions; note ;; that at this point we accept a couple of illegal ;; combinations which'll be sorted out later by the ;; converter (let* ((open-paren-pos (car (lexer-last-pos lexer))) ;; check if what follows "(?(" is a number (number (try-number lexer :no-whitespace-p t)) ;; make changes to extended-mode-p local (*extended-mode-p* *extended-mode-p*)) (declare (fixnum open-paren-pos)) (cond (number ;; condition is a number (i.e. refers to a ;; back-reference) (let* ((inner-close-token (get-token lexer)) (reg-expr (reg-expr lexer)) (close-token (get-token lexer))) (unless (eq inner-close-token :close-paren) (signal-syntax-error* (+ open-paren-pos 2) "Opening paren has no matching closing paren.")) (unless (eq close-token :close-paren) (signal-syntax-error* open-paren-pos "Opening paren has no matching closing paren.")) (list :branch number reg-expr))) (t ;; condition must be a full regex (actually a ;; look-behind or look-ahead); and here comes a ;; terrible kludge: instead of being cleanly ;; separated from the lexer, the parser pushes ;; back the lexer by one position, thereby ;; landing in the middle of the 'token' "(?(" - ;; yuck!! (decf (lexer-pos lexer)) (let* ((inner-reg-expr (group lexer)) (reg-expr (reg-expr lexer)) (close-token (get-token lexer))) (unless (eq close-token :close-paren) (signal-syntax-error* open-paren-pos "Opening paren has no matching closing paren.")) (list :branch inner-reg-expr reg-expr)))))) ((member open-token '(:open-paren :open-paren-colon :open-paren-greater :open-paren-equal :open-paren-exclamation :open-paren-less-equal :open-paren-less-exclamation :open-paren-less-letter) :test #'eq) ;; make changes to extended-mode-p local (let ((*extended-mode-p* *extended-mode-p*)) ;; we saw one of the six token representing opening ;; parentheses (let* ((open-paren-pos (car (lexer-last-pos lexer))) (register-name (when (eq open-token :open-paren-less-letter) (parse-register-name-aux lexer))) (reg-expr (reg-expr lexer)) (close-token (get-token lexer))) (when (or (eq open-token :open-paren) (eq open-token :open-paren-less-letter)) ;; if this is the "("")" or "(?"""")" production we have to ;; increment the register counter of the lexer (incf (lexer-reg lexer))) (unless (eq close-token :close-paren) ;; the token following must be the closing ;; parenthesis or this is a syntax error (signal-syntax-error* open-paren-pos "Opening paren has no matching closing paren.")) (if flags ;; if the lexer has returned a list of flags this must ;; have been the "(?:"")" production (cons :group (nconc flags (list reg-expr))) (if (eq open-token :open-paren-less-letter) (list :named-register ;; every string was reversed, so we have to ;; reverse it back to get the name (nreverse register-name) reg-expr) (list (case open-token ((:open-paren) :register) ((:open-paren-colon) :group) ((:open-paren-greater) :standalone) ((:open-paren-equal) :positive-lookahead) ((:open-paren-exclamation) :negative-lookahead) ((:open-paren-less-equal) :positive-lookbehind) ((:open-paren-less-exclamation) :negative-lookbehind)) reg-expr)))))) (t ;; this is the production; is ;; any token which passes START-OF-SUBEXPR-P (otherwise ;; parsing had already stopped in the SEQ method) open-token)))) (defun greedy-quant (lexer) "Parses and consumes a . The productions are: -> | where is parsed by the lexer function GET-QUANTIFIER. Will return or (:GREEDY-REPETITION )." (declare #.*standard-optimize-settings*) (let* ((group (group lexer)) (token (get-quantifier lexer))) (if token ;; if GET-QUANTIFIER returned a non-NIL value it's the ;; two-element list ( ) (list :greedy-repetition (first token) (second token) group) group))) (defun quant (lexer) "Parses and consumes a . The productions are: -> | \"?\". Will return the returned by GREEDY-QUANT and optionally change :GREEDY-REPETITION to :NON-GREEDY-REPETITION." (declare #.*standard-optimize-settings*) (let* ((greedy-quant (greedy-quant lexer)) (pos (lexer-pos lexer)) (next-char (next-char lexer))) (when next-char (if (char= next-char #\?) (setf (car greedy-quant) :non-greedy-repetition) (setf (lexer-pos lexer) pos))) greedy-quant)) (defun seq (lexer) "Parses and consumes a . The productions are: -> | . Will return or (:SEQUENCE )." (declare #.*standard-optimize-settings*) (flet ((make-array-from-two-chars (char1 char2) (let ((string (make-array 2 :element-type 'character :fill-pointer t :adjustable t))) (setf (aref string 0) char1) (setf (aref string 1) char2) string))) ;; Note that we're calling START-OF-SUBEXPR-P before we actually try ;; to parse a or in order to catch empty regular ;; expressions (if (start-of-subexpr-p lexer) (let ((quant (quant lexer))) (if (start-of-subexpr-p lexer) (let* ((seq (seq lexer)) (quant-is-char-p (characterp quant)) (seq-is-sequence-p (and (consp seq) (eq (first seq) :sequence)))) (cond ((and quant-is-char-p (characterp seq)) (make-array-from-two-chars seq quant)) ((and quant-is-char-p (stringp seq)) (vector-push-extend quant seq) seq) ((and quant-is-char-p seq-is-sequence-p (characterp (second seq))) (cond ((cddr seq) (setf (cdr seq) (cons (make-array-from-two-chars (second seq) quant) (cddr seq))) seq) (t (make-array-from-two-chars (second seq) quant)))) ((and quant-is-char-p seq-is-sequence-p (stringp (second seq))) (cond ((cddr seq) (setf (cdr seq) (cons (progn (vector-push-extend quant (second seq)) (second seq)) (cddr seq))) seq) (t (vector-push-extend quant (second seq)) (second seq)))) (seq-is-sequence-p ;; if is also a :SEQUENCE parse tree we merge ;; both lists into one to avoid unnecessary consing (setf (cdr seq) (cons quant (cdr seq))) seq) (t (list :sequence quant seq)))) quant)) :void))) (defun reg-expr (lexer) "Parses and consumes a , a complete regular expression. The productions are: -> | \"|\". Will return or (:ALTERNATION )." (declare #.*standard-optimize-settings*) (let ((pos (lexer-pos lexer))) (case (next-char lexer) ((nil) ;; if we didn't get any token we return :VOID which stands for ;; "empty regular expression" :void) ((#\|) ;; now check whether the expression started with a vertical ;; bar, i.e. - the left alternation - is empty (list :alternation :void (reg-expr lexer))) (otherwise ;; otherwise un-read the character we just saw and parse a ;; plus the character following it (setf (lexer-pos lexer) pos) (let* ((seq (seq lexer)) (pos (lexer-pos lexer))) (case (next-char lexer) ((nil) ;; no further character, just a seq) ((#\|) ;; if the character was a vertical bar, this is an ;; alternation and we have the second production (let ((reg-expr (reg-expr lexer))) (cond ((and (consp reg-expr) (eq (first reg-expr) :alternation)) ;; again we try to merge as above in SEQ (setf (cdr reg-expr) (cons seq (cdr reg-expr))) reg-expr) (t (list :alternation seq reg-expr))))) (otherwise ;; a character which is not a vertical bar - this is ;; either a syntax error or we're inside of a group and ;; the next character is a closing parenthesis; so we ;; just un-read the character and let another function ;; take care of it (setf (lexer-pos lexer) pos) seq))))))) (defun reverse-strings (parse-tree) "Recursively walks through PARSE-TREE and destructively reverses all strings in it." (declare #.*standard-optimize-settings*) (cond ((stringp parse-tree) (nreverse parse-tree)) ((consp parse-tree) (loop for parse-tree-rest on parse-tree while parse-tree-rest do (setf (car parse-tree-rest) (reverse-strings (car parse-tree-rest)))) parse-tree) (t parse-tree))) (defun parse-string (string) "Translate the regex string STRING into a parse tree." (declare #.*standard-optimize-settings*) (let* ((lexer (make-lexer string)) (parse-tree (reverse-strings (reg-expr lexer)))) ;; check whether we've consumed the whole regex string (if (end-of-string-p lexer) parse-tree (signal-syntax-error* (lexer-pos lexer) "Expected end of string.")))) cl-ppcre-2.0.3/regex-class-util.lisp0000644000175700010010000004771011254505513015532 0ustar ediNone;;; -*- Mode: LISP; Syntax: COMMON-LISP; Package: CL-PPCRE; Base: 10 -*- ;;; $Header: /usr/local/cvsrep/cl-ppcre/regex-class-util.lisp,v 1.9 2009/09/17 19:17:31 edi Exp $ ;;; This file contains some utility methods for REGEX objects. ;;; Copyright (c) 2002-2009, Dr. Edmund Weitz. All rights reserved. ;;; Redistribution and use in source and binary forms, with or without ;;; modification, are permitted provided that the following conditions ;;; are met: ;;; * Redistributions of source code must retain the above copyright ;;; notice, this list of conditions and the following disclaimer. ;;; * Redistributions in binary form must reproduce the above ;;; copyright notice, this list of conditions and the following ;;; disclaimer in the documentation and/or other materials ;;; provided with the distribution. ;;; THIS SOFTWARE IS PROVIDED BY THE AUTHOR 'AS IS' AND ANY EXPRESSED ;;; OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED ;;; WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ;;; ARE DISCLAIMED. IN NO EVENT SHALL THE AUTHOR BE LIABLE FOR ANY ;;; DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL ;;; DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE ;;; GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS ;;; INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, ;;; WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING ;;; NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE OF THIS ;;; SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. (in-package :cl-ppcre) ;;; The following four methods allow a VOID object to behave like a ;;; zero-length STR object (only readers needed) (defmethod len ((void void)) (declare #.*standard-optimize-settings*) 0) (defmethod str ((void void)) (declare #.*standard-optimize-settings*) "") (defmethod skip ((void void)) (declare #.*standard-optimize-settings*) nil) (defmethod start-of-end-string-p ((void void)) (declare #.*standard-optimize-settings*) nil) (defgeneric case-mode (regex old-case-mode) (declare #.*standard-optimize-settings*) (:documentation "Utility function used by the optimizer (see GATHER-STRINGS). Returns a keyword denoting the case-(in)sensitivity of a STR or its second argument if the STR has length 0. Returns NIL for REGEX objects which are not of type STR.")) (defmethod case-mode ((str str) old-case-mode) (declare #.*standard-optimize-settings*) (cond ((zerop (len str)) old-case-mode) ((case-insensitive-p str) :case-insensitive) (t :case-sensitive))) (defmethod case-mode ((regex regex) old-case-mode) (declare #.*standard-optimize-settings*) (declare (ignore old-case-mode)) nil) (defgeneric copy-regex (regex) (declare #.*standard-optimize-settings*) (:documentation "Implements a deep copy of a REGEX object.")) (defmethod copy-regex ((anchor anchor)) (declare #.*standard-optimize-settings*) (make-instance 'anchor :startp (startp anchor) :multi-line-p (multi-line-p anchor) :no-newline-p (no-newline-p anchor))) (defmethod copy-regex ((everything everything)) (declare #.*standard-optimize-settings*) (make-instance 'everything :single-line-p (single-line-p everything))) (defmethod copy-regex ((word-boundary word-boundary)) (declare #.*standard-optimize-settings*) (make-instance 'word-boundary :negatedp (negatedp word-boundary))) (defmethod copy-regex ((void void)) (declare #.*standard-optimize-settings*) (make-instance 'void)) (defmethod copy-regex ((lookahead lookahead)) (declare #.*standard-optimize-settings*) (make-instance 'lookahead :regex (copy-regex (regex lookahead)) :positivep (positivep lookahead))) (defmethod copy-regex ((seq seq)) (declare #.*standard-optimize-settings*) (make-instance 'seq :elements (mapcar #'copy-regex (elements seq)))) (defmethod copy-regex ((alternation alternation)) (declare #.*standard-optimize-settings*) (make-instance 'alternation :choices (mapcar #'copy-regex (choices alternation)))) (defmethod copy-regex ((branch branch)) (declare #.*standard-optimize-settings*) (with-slots (test) branch (make-instance 'branch :test (if (typep test 'regex) (copy-regex test) test) :then-regex (copy-regex (then-regex branch)) :else-regex (copy-regex (else-regex branch))))) (defmethod copy-regex ((lookbehind lookbehind)) (declare #.*standard-optimize-settings*) (make-instance 'lookbehind :regex (copy-regex (regex lookbehind)) :positivep (positivep lookbehind) :len (len lookbehind))) (defmethod copy-regex ((repetition repetition)) (declare #.*standard-optimize-settings*) (make-instance 'repetition :regex (copy-regex (regex repetition)) :greedyp (greedyp repetition) :minimum (minimum repetition) :maximum (maximum repetition) :min-len (min-len repetition) :len (len repetition) :contains-register-p (contains-register-p repetition))) (defmethod copy-regex ((register register)) (declare #.*standard-optimize-settings*) (make-instance 'register :regex (copy-regex (regex register)) :num (num register) :name (name register))) (defmethod copy-regex ((standalone standalone)) (declare #.*standard-optimize-settings*) (make-instance 'standalone :regex (copy-regex (regex standalone)))) (defmethod copy-regex ((back-reference back-reference)) (declare #.*standard-optimize-settings*) (make-instance 'back-reference :num (num back-reference) :case-insensitive-p (case-insensitive-p back-reference))) (defmethod copy-regex ((char-class char-class)) (declare #.*standard-optimize-settings*) (make-instance 'char-class :test-function (test-function char-class))) (defmethod copy-regex ((str str)) (declare #.*standard-optimize-settings*) (make-instance 'str :str (str str) :case-insensitive-p (case-insensitive-p str))) (defmethod copy-regex ((filter filter)) (declare #.*standard-optimize-settings*) (make-instance 'filter :fn (fn filter) :len (len filter))) ;;; Note that COPY-REGEX and REMOVE-REGISTERS could have easily been ;;; wrapped into one function. Maybe in the next release... ;;; Further note that this function is used by CONVERT to factor out ;;; complicated repetitions, i.e. cases like ;;; (a)* -> (?:a*(a))? ;;; This won't work for, say, ;;; ((a)|(b))* -> (?:(?:a|b)*((a)|(b)))? ;;; and therefore we stop REGISTER removal once we see an ALTERNATION. (defgeneric remove-registers (regex) (declare #.*standard-optimize-settings*) (:documentation "Returns a deep copy of a REGEX (see COPY-REGEX) and optionally removes embedded REGISTER objects if possible and if the special variable REMOVE-REGISTERS-P is true.")) (defmethod remove-registers ((register register)) (declare #.*standard-optimize-settings*) (declare (special remove-registers-p reg-seen)) (cond (remove-registers-p (remove-registers (regex register))) (t ;; mark REG-SEEN as true so enclosing REPETITION objects ;; (see method below) know if they contain a register or not (setq reg-seen t) (copy-regex register)))) (defmethod remove-registers ((repetition repetition)) (declare #.*standard-optimize-settings*) (let* (reg-seen (inner-regex (remove-registers (regex repetition)))) ;; REMOVE-REGISTERS will set REG-SEEN (see method above) if ;; (REGEX REPETITION) contains a REGISTER (declare (special reg-seen)) (make-instance 'repetition :regex inner-regex :greedyp (greedyp repetition) :minimum (minimum repetition) :maximum (maximum repetition) :min-len (min-len repetition) :len (len repetition) :contains-register-p reg-seen))) (defmethod remove-registers ((standalone standalone)) (declare #.*standard-optimize-settings*) (make-instance 'standalone :regex (remove-registers (regex standalone)))) (defmethod remove-registers ((lookahead lookahead)) (declare #.*standard-optimize-settings*) (make-instance 'lookahead :regex (remove-registers (regex lookahead)) :positivep (positivep lookahead))) (defmethod remove-registers ((lookbehind lookbehind)) (declare #.*standard-optimize-settings*) (make-instance 'lookbehind :regex (remove-registers (regex lookbehind)) :positivep (positivep lookbehind) :len (len lookbehind))) (defmethod remove-registers ((branch branch)) (declare #.*standard-optimize-settings*) (with-slots (test) branch (make-instance 'branch :test (if (typep test 'regex) (remove-registers test) test) :then-regex (remove-registers (then-regex branch)) :else-regex (remove-registers (else-regex branch))))) (defmethod remove-registers ((alternation alternation)) (declare #.*standard-optimize-settings*) (declare (special remove-registers-p)) ;; an ALTERNATION, so we can't remove REGISTER objects further down (setq remove-registers-p nil) (copy-regex alternation)) (defmethod remove-registers ((regex regex)) (declare #.*standard-optimize-settings*) (copy-regex regex)) (defmethod remove-registers ((seq seq)) (declare #.*standard-optimize-settings*) (make-instance 'seq :elements (mapcar #'remove-registers (elements seq)))) (defgeneric everythingp (regex) (declare #.*standard-optimize-settings*) (:documentation "Returns an EVERYTHING object if REGEX is equivalent to this object, otherwise NIL. So, \"(.){1}\" would return true \(i.e. the object corresponding to \".\", for example.")) (defmethod everythingp ((seq seq)) (declare #.*standard-optimize-settings*) ;; we might have degenerate cases like (:SEQUENCE :VOID ...) ;; due to the parsing process (let ((cleaned-elements (remove-if #'(lambda (element) (typep element 'void)) (elements seq)))) (and (= 1 (length cleaned-elements)) (everythingp (first cleaned-elements))))) (defmethod everythingp ((alternation alternation)) (declare #.*standard-optimize-settings*) (with-slots (choices) alternation (and (= 1 (length choices)) ;; this is unlikely to happen for human-generated regexes, ;; but machine-generated ones might look like this (everythingp (first choices))))) (defmethod everythingp ((repetition repetition)) (declare #.*standard-optimize-settings*) (with-slots (maximum minimum regex) repetition (and maximum (= 1 minimum maximum) ;; treat "{1,1}" like "" (everythingp regex)))) (defmethod everythingp ((register register)) (declare #.*standard-optimize-settings*) (everythingp (regex register))) (defmethod everythingp ((standalone standalone)) (declare #.*standard-optimize-settings*) (everythingp (regex standalone))) (defmethod everythingp ((everything everything)) (declare #.*standard-optimize-settings*) everything) (defmethod everythingp ((regex regex)) (declare #.*standard-optimize-settings*) ;; the general case for ANCHOR, BACK-REFERENCE, BRANCH, CHAR-CLASS, ;; LOOKAHEAD, LOOKBEHIND, STR, VOID, FILTER, and WORD-BOUNDARY nil) (defgeneric regex-length (regex) (declare #.*standard-optimize-settings*) (:documentation "Return the length of REGEX if it is fixed, NIL otherwise.")) (defmethod regex-length ((seq seq)) (declare #.*standard-optimize-settings*) ;; simply add all inner lengths unless one of them is NIL (loop for sub-regex in (elements seq) for len = (regex-length sub-regex) if (not len) do (return nil) sum len)) (defmethod regex-length ((alternation alternation)) (declare #.*standard-optimize-settings*) ;; only return a true value if all inner lengths are non-NIL and ;; mutually equal (loop for sub-regex in (choices alternation) for old-len = nil then len for len = (regex-length sub-regex) if (or (not len) (and old-len (/= len old-len))) do (return nil) finally (return len))) (defmethod regex-length ((branch branch)) (declare #.*standard-optimize-settings*) ;; only return a true value if both alternations have a length and ;; if they're equal (let ((then-length (regex-length (then-regex branch)))) (and then-length (eql then-length (regex-length (else-regex branch))) then-length))) (defmethod regex-length ((repetition repetition)) (declare #.*standard-optimize-settings*) ;; we can only compute the length of a REPETITION object if the ;; number of repetitions is fixed; note that we don't call ;; REGEX-LENGTH for the inner regex, we assume that the LEN slot is ;; always set correctly (with-slots (len minimum maximum) repetition (if (and len (eql minimum maximum)) (* minimum len) nil))) (defmethod regex-length ((register register)) (declare #.*standard-optimize-settings*) (regex-length (regex register))) (defmethod regex-length ((standalone standalone)) (declare #.*standard-optimize-settings*) (regex-length (regex standalone))) (defmethod regex-length ((back-reference back-reference)) (declare #.*standard-optimize-settings*) ;; with enough effort we could possibly do better here, but ;; currently we just give up and return NIL nil) (defmethod regex-length ((char-class char-class)) (declare #.*standard-optimize-settings*) 1) (defmethod regex-length ((everything everything)) (declare #.*standard-optimize-settings*) 1) (defmethod regex-length ((str str)) (declare #.*standard-optimize-settings*) (len str)) (defmethod regex-length ((filter filter)) (declare #.*standard-optimize-settings*) (len filter)) (defmethod regex-length ((regex regex)) (declare #.*standard-optimize-settings*) ;; the general case for ANCHOR, LOOKAHEAD, LOOKBEHIND, VOID, and ;; WORD-BOUNDARY (which all have zero-length) 0) (defgeneric regex-min-length (regex) (declare #.*standard-optimize-settings*) (:documentation "Returns the minimal length of REGEX.")) (defmethod regex-min-length ((seq seq)) (declare #.*standard-optimize-settings*) ;; simply add all inner minimal lengths (loop for sub-regex in (elements seq) for len = (regex-min-length sub-regex) sum len)) (defmethod regex-min-length ((alternation alternation)) (declare #.*standard-optimize-settings*) ;; minimal length of an alternation is the minimal length of the ;; "shortest" element (loop for sub-regex in (choices alternation) for len = (regex-min-length sub-regex) minimize len)) (defmethod regex-min-length ((branch branch)) (declare #.*standard-optimize-settings*) ;; minimal length of both alternations (min (regex-min-length (then-regex branch)) (regex-min-length (else-regex branch)))) (defmethod regex-min-length ((repetition repetition)) (declare #.*standard-optimize-settings*) ;; obviously the product of the inner minimal length and the minimal ;; number of repetitions (* (minimum repetition) (min-len repetition))) (defmethod regex-min-length ((register register)) (declare #.*standard-optimize-settings*) (regex-min-length (regex register))) (defmethod regex-min-length ((standalone standalone)) (declare #.*standard-optimize-settings*) (regex-min-length (regex standalone))) (defmethod regex-min-length ((char-class char-class)) (declare #.*standard-optimize-settings*) 1) (defmethod regex-min-length ((everything everything)) (declare #.*standard-optimize-settings*) 1) (defmethod regex-min-length ((str str)) (declare #.*standard-optimize-settings*) (len str)) (defmethod regex-min-length ((filter filter)) (declare #.*standard-optimize-settings*) (or (len filter) 0)) (defmethod regex-min-length ((regex regex)) (declare #.*standard-optimize-settings*) ;; the general case for ANCHOR, BACK-REFERENCE, LOOKAHEAD, ;; LOOKBEHIND, VOID, and WORD-BOUNDARY 0) (defgeneric compute-offsets (regex start-pos) (declare #.*standard-optimize-settings*) (:documentation "Returns the offset the following regex would have relative to START-POS or NIL if we can't compute it. Sets the OFFSET slot of REGEX to START-POS if REGEX is a STR. May also affect OFFSET slots of STR objects further down the tree.")) ;; note that we're actually only interested in the offset of ;; "top-level" STR objects (see ADVANCE-FN in the SCAN function) so we ;; can stop at variable-length alternations and don't need to descend ;; into repetitions (defmethod compute-offsets ((seq seq) start-pos) (declare #.*standard-optimize-settings*) (loop for element in (elements seq) ;; advance offset argument for next call while looping through ;; the elements for pos = start-pos then curr-offset for curr-offset = (compute-offsets element pos) while curr-offset finally (return curr-offset))) (defmethod compute-offsets ((alternation alternation) start-pos) (declare #.*standard-optimize-settings*) (loop for choice in (choices alternation) for old-offset = nil then curr-offset for curr-offset = (compute-offsets choice start-pos) ;; we stop immediately if two alternations don't result in the ;; same offset if (or (not curr-offset) (and old-offset (/= curr-offset old-offset))) do (return nil) finally (return curr-offset))) (defmethod compute-offsets ((branch branch) start-pos) (declare #.*standard-optimize-settings*) ;; only return offset if both alternations have equal value (let ((then-offset (compute-offsets (then-regex branch) start-pos))) (and then-offset (eql then-offset (compute-offsets (else-regex branch) start-pos)) then-offset))) (defmethod compute-offsets ((repetition repetition) start-pos) (declare #.*standard-optimize-settings*) ;; no need to descend into the inner regex (with-slots (len minimum maximum) repetition (if (and len (eq minimum maximum)) ;; fixed number of repetitions, so we know how to proceed (+ start-pos (* minimum len)) ;; otherwise return NIL nil))) (defmethod compute-offsets ((register register) start-pos) (declare #.*standard-optimize-settings*) (compute-offsets (regex register) start-pos)) (defmethod compute-offsets ((standalone standalone) start-pos) (declare #.*standard-optimize-settings*) (compute-offsets (regex standalone) start-pos)) (defmethod compute-offsets ((char-class char-class) start-pos) (declare #.*standard-optimize-settings*) (1+ start-pos)) (defmethod compute-offsets ((everything everything) start-pos) (declare #.*standard-optimize-settings*) (1+ start-pos)) (defmethod compute-offsets ((str str) start-pos) (declare #.*standard-optimize-settings*) (setf (offset str) start-pos) (+ start-pos (len str))) (defmethod compute-offsets ((back-reference back-reference) start-pos) (declare #.*standard-optimize-settings*) ;; with enough effort we could possibly do better here, but ;; currently we just give up and return NIL (declare (ignore start-pos)) nil) (defmethod compute-offsets ((filter filter) start-pos) (declare #.*standard-optimize-settings*) (let ((len (len filter))) (if len (+ start-pos len) nil))) (defmethod compute-offsets ((regex regex) start-pos) (declare #.*standard-optimize-settings*) ;; the general case for ANCHOR, LOOKAHEAD, LOOKBEHIND, VOID, and ;; WORD-BOUNDARY (which all have zero-length) start-pos) cl-ppcre-2.0.3/regex-class.lisp0000644000175700010010000002354211271772157014565 0ustar ediNone;;; -*- Mode: LISP; Syntax: COMMON-LISP; Package: CL-PPCRE; Base: 10 -*- ;;; $Header: /usr/local/cvsrep/cl-ppcre/regex-class.lisp,v 1.44 2009/10/28 07:36:15 edi Exp $ ;;; This file defines the REGEX class. REGEX objects are used to ;;; represent the (transformed) parse trees internally ;;; Copyright (c) 2002-2009, Dr. Edmund Weitz. All rights reserved. ;;; Redistribution and use in source and binary forms, with or without ;;; modification, are permitted provided that the following conditions ;;; are met: ;;; * Redistributions of source code must retain the above copyright ;;; notice, this list of conditions and the following disclaimer. ;;; * Redistributions in binary form must reproduce the above ;;; copyright notice, this list of conditions and the following ;;; disclaimer in the documentation and/or other materials ;;; provided with the distribution. ;;; THIS SOFTWARE IS PROVIDED BY THE AUTHOR 'AS IS' AND ANY EXPRESSED ;;; OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED ;;; WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ;;; ARE DISCLAIMED. IN NO EVENT SHALL THE AUTHOR BE LIABLE FOR ANY ;;; DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL ;;; DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE ;;; GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS ;;; INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, ;;; WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING ;;; NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE OF THIS ;;; SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. (in-package :cl-ppcre) (defclass regex () () (:documentation "The REGEX base class. All other classes inherit from this one.")) (defclass seq (regex) ((elements :initarg :elements :accessor elements :type cons :documentation "A list of REGEX objects.")) (:documentation "SEQ objects represents sequences of regexes. \(Like \"ab\" is the sequence of \"a\" and \"b\".)")) (defclass alternation (regex) ((choices :initarg :choices :accessor choices :type cons :documentation "A list of REGEX objects")) (:documentation "ALTERNATION objects represent alternations of regexes. \(Like \"a|b\" ist the alternation of \"a\" or \"b\".)")) (defclass lookahead (regex) ((regex :initarg :regex :accessor regex :documentation "The REGEX object we're checking.") (positivep :initarg :positivep :reader positivep :documentation "Whether this assertion is positive.")) (:documentation "LOOKAHEAD objects represent look-ahead assertions.")) (defclass lookbehind (regex) ((regex :initarg :regex :accessor regex :documentation "The REGEX object we're checking.") (positivep :initarg :positivep :reader positivep :documentation "Whether this assertion is positive.") (len :initarg :len :accessor len :type fixnum :documentation "The \(fixed) length of the enclosed regex.")) (:documentation "LOOKBEHIND objects represent look-behind assertions.")) (defclass repetition (regex) ((regex :initarg :regex :accessor regex :documentation "The REGEX that's repeated.") (greedyp :initarg :greedyp :reader greedyp :documentation "Whether the repetition is greedy.") (minimum :initarg :minimum :accessor minimum :type fixnum :documentation "The minimal number of repetitions.") (maximum :initarg :maximum :accessor maximum :documentation "The maximal number of repetitions. Can be NIL for unbounded.") (min-len :initarg :min-len :reader min-len :documentation "The minimal length of the enclosed regex.") (len :initarg :len :reader len :documentation "The length of the enclosed regex. NIL if unknown.") (min-rest :initform 0 :accessor min-rest :type fixnum :documentation "The minimal number of characters which must appear after this repetition.") (contains-register-p :initarg :contains-register-p :reader contains-register-p :documentation "Whether the regex contains a register.")) (:documentation "REPETITION objects represent repetitions of regexes.")) (defclass register (regex) ((regex :initarg :regex :accessor regex :documentation "The inner regex.") (num :initarg :num :reader num :type fixnum :documentation "The number of this register, starting from 0. This is the index into *REGS-START* and *REGS-END*.") (name :initarg :name :reader name :documentation "Name of this register or NIL.")) (:documentation "REGISTER objects represent register groups.")) (defclass standalone (regex) ((regex :initarg :regex :accessor regex :documentation "The inner regex.")) (:documentation "A standalone regular expression.")) (defclass back-reference (regex) ((num :initarg :num :accessor num :type fixnum :documentation "The number of the register this reference refers to.") (name :initarg :name :accessor name :documentation "The name of the register this reference refers to or NIL.") (case-insensitive-p :initarg :case-insensitive-p :reader case-insensitive-p :documentation "Whether we check case-insensitively.")) (:documentation "BACK-REFERENCE objects represent backreferences.")) (defclass char-class (regex) ((test-function :initarg :test-function :reader test-function :type (or function symbol nil) :documentation "A unary function \(accepting a character) which stands in for the character class and does the work of checking whether a character belongs to the class.")) (:documentation "CHAR-CLASS objects represent character classes.")) (defclass str (regex) ((str :initarg :str :accessor str :type string :documentation "The actual string.") (len :initform 0 :accessor len :type fixnum :documentation "The length of the string.") (case-insensitive-p :initarg :case-insensitive-p :reader case-insensitive-p :documentation "If we match case-insensitively.") (offset :initform nil :accessor offset :documentation "Offset from the left of the whole parse tree. The first regex has offset 0. NIL if unknown, i.e. behind a variable-length regex.") (skip :initform nil :initarg :skip :accessor skip :documentation "If we can avoid testing for this string because the SCAN function has done this already.") (start-of-end-string-p :initform nil :accessor start-of-end-string-p :documentation "If this is the unique STR which starts END-STRING (a slot of MATCHER).")) (:documentation "STR objects represent string.")) (defclass anchor (regex) ((startp :initarg :startp :reader startp :documentation "Whether this is a \"start anchor\".") (multi-line-p :initarg :multi-line-p :initform nil :reader multi-line-p :documentation "Whether we're in multi-line mode, i.e. whether each #\\Newline is surrounded by anchors.") (no-newline-p :initarg :no-newline-p :initform nil :reader no-newline-p :documentation "Whether we ignore #\\Newline at the end.")) (:documentation "ANCHOR objects represent anchors like \"^\" or \"$\".")) (defclass everything (regex) ((single-line-p :initarg :single-line-p :reader single-line-p :documentation "Whether we're in single-line mode, i.e. whether we also match #\\Newline.")) (:documentation "EVERYTHING objects represent regexes matching \"everything\", i.e. dots.")) (defclass word-boundary (regex) ((negatedp :initarg :negatedp :reader negatedp :documentation "Whether we mean the opposite, i.e. no word-boundary.")) (:documentation "WORD-BOUNDARY objects represent word-boundary assertions.")) (defclass branch (regex) ((test :initarg :test :accessor test :documentation "The test of this branch, one of LOOKAHEAD, LOOKBEHIND, or a number.") (then-regex :initarg :then-regex :accessor then-regex :documentation "The regex that's to be matched if the test succeeds.") (else-regex :initarg :else-regex :initform (make-instance 'void) :accessor else-regex :documentation "The regex that's to be matched if the test fails.")) (:documentation "BRANCH objects represent Perl's conditional regular expressions.")) (defclass filter (regex) ((fn :initarg :fn :accessor fn :type (or function symbol) :documentation "The user-defined function.") (len :initarg :len :reader len :documentation "The fixed length of this filter or NIL.")) (:documentation "FILTER objects represent arbitrary functions defined by the user.")) (defclass void (regex) () (:documentation "VOID objects represent empty regular expressions.")) (defmethod initialize-instance :after ((str str) &rest init-args) (declare #.*standard-optimize-settings*) (declare (ignore init-args)) "Automatically computes the length of a STR after initialization." (let ((str-slot (slot-value str 'str))) (unless (typep str-slot #-:lispworks 'simple-string #+:lispworks 'lw:simple-text-string) (setf (slot-value str 'str) (coerce str-slot #-:lispworks 'simple-string #+:lispworks 'lw:simple-text-string)))) (setf (len str) (length (str str)))) cl-ppcre-2.0.3/repetition-closures.lisp0000644000175700010010000012055011254505513016353 0ustar ediNone;;; -*- Mode: LISP; Syntax: COMMON-LISP; Package: CL-PPCRE; Base: 10 -*- ;;; $Header: /usr/local/cvsrep/cl-ppcre/repetition-closures.lisp,v 1.34 2009/09/17 19:17:31 edi Exp $ ;;; This is actually a part of closures.lisp which we put into a ;;; separate file because it is rather complex. We only deal with ;;; REPETITIONs here. Note that this part of the code contains some ;;; rather crazy micro-optimizations which were introduced to be as ;;; competitive with Perl as possible in tight loops. ;;; Copyright (c) 2002-2009, Dr. Edmund Weitz. All rights reserved. ;;; Redistribution and use in source and binary forms, with or without ;;; modification, are permitted provided that the following conditions ;;; are met: ;;; * Redistributions of source code must retain the above copyright ;;; notice, this list of conditions and the following disclaimer. ;;; * Redistributions in binary form must reproduce the above ;;; copyright notice, this list of conditions and the following ;;; disclaimer in the documentation and/or other materials ;;; provided with the distribution. ;;; THIS SOFTWARE IS PROVIDED BY THE AUTHOR 'AS IS' AND ANY EXPRESSED ;;; OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED ;;; WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ;;; ARE DISCLAIMED. IN NO EVENT SHALL THE AUTHOR BE LIABLE FOR ANY ;;; DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL ;;; DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE ;;; GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS ;;; INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, ;;; WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING ;;; NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE OF THIS ;;; SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. (in-package :cl-ppcre) (defmacro incf-after (place &optional (delta 1) &environment env) "Utility macro inspired by C's \"place++\", i.e. first return the value of PLACE and afterwards increment it by DELTA." (with-unique-names (%temp) (multiple-value-bind (vars vals store-vars writer-form reader-form) (get-setf-expansion place env) `(let* (,@(mapcar #'list vars vals) (,%temp ,reader-form) (,(car store-vars) (+ ,%temp ,delta))) ,writer-form ,%temp)))) ;; code for greedy repetitions with minimum zero (defmacro greedy-constant-length-closure (check-curr-pos) "This is the template for simple greedy repetitions (where simple means that the minimum number of repetitions is zero, that the inner regex to be checked is of fixed length LEN, and that it doesn't contain registers, i.e. there's no need for backtracking). CHECK-CURR-POS is a form which checks whether the inner regex of the repetition matches at CURR-POS." `(if maximum (lambda (start-pos) (declare (fixnum start-pos maximum)) ;; because we know LEN we know in advance where to stop at the ;; latest; we also take into consideration MIN-REST, i.e. the ;; minimal length of the part behind the repetition (let ((target-end-pos (min (1+ (- *end-pos* len min-rest)) ;; don't go further than MAXIMUM ;; repetitions, of course (+ start-pos (the fixnum (* len maximum))))) (curr-pos start-pos)) (declare (fixnum target-end-pos curr-pos)) (block greedy-constant-length-matcher ;; we use an ugly TAGBODY construct because this might be a ;; tight loop and this version is a bit faster than our LOOP ;; version (at least in CMUCL) (tagbody forward-loop ;; first go forward as far as possible, i.e. while ;; the inner regex matches (when (>= curr-pos target-end-pos) (go backward-loop)) (when ,check-curr-pos (incf curr-pos len) (go forward-loop)) backward-loop ;; now go back LEN steps each until we're able to match ;; the rest of the regex (when (< curr-pos start-pos) (return-from greedy-constant-length-matcher nil)) (let ((result (funcall next-fn curr-pos))) (when result (return-from greedy-constant-length-matcher result))) (decf curr-pos len) (go backward-loop))))) ;; basically the same code; it's just a bit easier because we're ;; not bounded by MAXIMUM (lambda (start-pos) (declare (fixnum start-pos)) (let ((target-end-pos (1+ (- *end-pos* len min-rest))) (curr-pos start-pos)) (declare (fixnum target-end-pos curr-pos)) (block greedy-constant-length-matcher (tagbody forward-loop (when (>= curr-pos target-end-pos) (go backward-loop)) (when ,check-curr-pos (incf curr-pos len) (go forward-loop)) backward-loop (when (< curr-pos start-pos) (return-from greedy-constant-length-matcher nil)) (let ((result (funcall next-fn curr-pos))) (when result (return-from greedy-constant-length-matcher result))) (decf curr-pos len) (go backward-loop))))))) (defun create-greedy-everything-matcher (maximum min-rest next-fn) "Creates a closure which just matches as far ahead as possible, i.e. a closure for a dot in single-line mode." (declare #.*standard-optimize-settings*) (declare (fixnum min-rest) (function next-fn)) (if maximum (lambda (start-pos) (declare (fixnum start-pos maximum)) ;; because we know LEN we know in advance where to stop at the ;; latest; we also take into consideration MIN-REST, i.e. the ;; minimal length of the part behind the repetition (let ((target-end-pos (min (+ start-pos maximum) (- *end-pos* min-rest)))) (declare (fixnum target-end-pos)) ;; start from the highest possible position and go backward ;; until we're able to match the rest of the regex (loop for curr-pos of-type fixnum from target-end-pos downto start-pos thereis (funcall next-fn curr-pos)))) ;; basically the same code; it's just a bit easier because we're ;; not bounded by MAXIMUM (lambda (start-pos) (declare (fixnum start-pos)) (let ((target-end-pos (- *end-pos* min-rest))) (declare (fixnum target-end-pos)) (loop for curr-pos of-type fixnum from target-end-pos downto start-pos thereis (funcall next-fn curr-pos)))))) (defgeneric create-greedy-constant-length-matcher (repetition next-fn) (declare #.*standard-optimize-settings*) (:documentation "Creates a closure which tries to match REPETITION. It is assumed that REPETITION is greedy and the minimal number of repetitions is zero. It is furthermore assumed that the inner regex of REPETITION is of fixed length and doesn't contain registers.")) (defmethod create-greedy-constant-length-matcher ((repetition repetition) next-fn) (declare #.*standard-optimize-settings*) (let ((len (len repetition)) (maximum (maximum repetition)) (regex (regex repetition)) (min-rest (min-rest repetition))) (declare (fixnum len min-rest) (function next-fn)) (cond ((zerop len) ;; inner regex has zero-length, so we can discard it ;; completely next-fn) (t ;; now first try to optimize for a couple of common cases (typecase regex (str (let ((str (str regex))) (if (= 1 len) ;; a single character (let ((chr (schar str 0))) (if (case-insensitive-p regex) (greedy-constant-length-closure (char-equal chr (schar *string* curr-pos))) (greedy-constant-length-closure (char= chr (schar *string* curr-pos))))) ;; a string (if (case-insensitive-p regex) (greedy-constant-length-closure (*string*-equal str curr-pos (+ curr-pos len) 0 len)) (greedy-constant-length-closure (*string*= str curr-pos (+ curr-pos len) 0 len)))))) (char-class ;; a character class (insert-char-class-tester (regex (schar *string* curr-pos)) (greedy-constant-length-closure (char-class-test)))) (everything ;; an EVERYTHING object, i.e. a dot (if (single-line-p regex) (create-greedy-everything-matcher maximum min-rest next-fn) (greedy-constant-length-closure (char/= #\Newline (schar *string* curr-pos))))) (t ;; the general case - we build an inner matcher which ;; just checks for immediate success, i.e. NEXT-FN is ;; #'IDENTITY (let ((inner-matcher (create-matcher-aux regex #'identity))) (declare (function inner-matcher)) (greedy-constant-length-closure (funcall inner-matcher curr-pos))))))))) (defgeneric create-greedy-no-zero-matcher (repetition next-fn) (declare #.*standard-optimize-settings*) (:documentation "Creates a closure which tries to match REPETITION. It is assumed that REPETITION is greedy and the minimal number of repetitions is zero. It is furthermore assumed that the inner regex of REPETITION can never match a zero-length string \(or instead the maximal number of repetitions is 1).")) (defmethod create-greedy-no-zero-matcher ((repetition repetition) next-fn) (declare #.*standard-optimize-settings*) (let ((maximum (maximum repetition)) ;; REPEAT-MATCHER is part of the closure's environment but it ;; can only be defined after GREEDY-AUX is defined repeat-matcher) (declare (function next-fn)) (cond ((eql maximum 1) ;; this is essentially like the next case but with a known ;; MAXIMUM of 1 we can get away without a counter; note that ;; we always arrive here if CONVERT optimizes * to ;; (?:*)? (setq repeat-matcher (create-matcher-aux (regex repetition) next-fn)) (lambda (start-pos) (declare (function repeat-matcher)) (or (funcall repeat-matcher start-pos) (funcall next-fn start-pos)))) (maximum ;; we make a reservation for our slot in *REPEAT-COUNTERS* ;; because we need to keep track whether we've reached MAXIMUM ;; repetitions (let ((rep-num (incf-after *rep-num*))) (flet ((greedy-aux (start-pos) (declare (fixnum start-pos maximum rep-num) (function repeat-matcher)) ;; the actual matcher which first tries to match the ;; inner regex of REPETITION (if we haven't done so ;; too often) and on failure calls NEXT-FN (or (and (< (aref *repeat-counters* rep-num) maximum) (incf (aref *repeat-counters* rep-num)) ;; note that REPEAT-MATCHER will call ;; GREEDY-AUX again recursively (prog1 (funcall repeat-matcher start-pos) (decf (aref *repeat-counters* rep-num)))) (funcall next-fn start-pos)))) ;; create a closure to match the inner regex and to ;; implement backtracking via GREEDY-AUX (setq repeat-matcher (create-matcher-aux (regex repetition) #'greedy-aux)) ;; the closure we return is just a thin wrapper around ;; GREEDY-AUX to initialize the repetition counter (lambda (start-pos) (declare (fixnum start-pos)) (setf (aref *repeat-counters* rep-num) 0) (greedy-aux start-pos))))) (t ;; easier code because we're not bounded by MAXIMUM, but ;; basically the same (flet ((greedy-aux (start-pos) (declare (fixnum start-pos) (function repeat-matcher)) (or (funcall repeat-matcher start-pos) (funcall next-fn start-pos)))) (setq repeat-matcher (create-matcher-aux (regex repetition) #'greedy-aux)) #'greedy-aux))))) (defgeneric create-greedy-matcher (repetition next-fn) (declare #.*standard-optimize-settings*) (:documentation "Creates a closure which tries to match REPETITION. It is assumed that REPETITION is greedy and the minimal number of repetitions is zero.")) (defmethod create-greedy-matcher ((repetition repetition) next-fn) (declare #.*standard-optimize-settings*) (let ((maximum (maximum repetition)) ;; we make a reservation for our slot in *LAST-POS-STORES* because ;; we have to watch out for endless loops as the inner regex might ;; match zero-length strings (zero-length-num (incf-after *zero-length-num*)) ;; REPEAT-MATCHER is part of the closure's environment but it ;; can only be defined after GREEDY-AUX is defined repeat-matcher) (declare (fixnum zero-length-num) (function next-fn)) (cond (maximum ;; we make a reservation for our slot in *REPEAT-COUNTERS* ;; because we need to keep track whether we've reached MAXIMUM ;; repetitions (let ((rep-num (incf-after *rep-num*))) (flet ((greedy-aux (start-pos) ;; the actual matcher which first tries to match the ;; inner regex of REPETITION (if we haven't done so ;; too often) and on failure calls NEXT-FN (declare (fixnum start-pos maximum rep-num) (function repeat-matcher)) (let ((old-last-pos (svref *last-pos-stores* zero-length-num))) (when (and old-last-pos (= (the fixnum old-last-pos) start-pos)) ;; stop immediately if we've been here before, ;; i.e. if the last attempt matched a zero-length ;; string (return-from greedy-aux (funcall next-fn start-pos))) ;; otherwise remember this position for the next ;; repetition (setf (svref *last-pos-stores* zero-length-num) start-pos) (or (and (< (aref *repeat-counters* rep-num) maximum) (incf (aref *repeat-counters* rep-num)) ;; note that REPEAT-MATCHER will call ;; GREEDY-AUX again recursively (prog1 (funcall repeat-matcher start-pos) (decf (aref *repeat-counters* rep-num)) (setf (svref *last-pos-stores* zero-length-num) old-last-pos))) (funcall next-fn start-pos))))) ;; create a closure to match the inner regex and to ;; implement backtracking via GREEDY-AUX (setq repeat-matcher (create-matcher-aux (regex repetition) #'greedy-aux)) ;; the closure we return is just a thin wrapper around ;; GREEDY-AUX to initialize the repetition counter and our ;; slot in *LAST-POS-STORES* (lambda (start-pos) (declare (fixnum start-pos)) (setf (aref *repeat-counters* rep-num) 0 (svref *last-pos-stores* zero-length-num) nil) (greedy-aux start-pos))))) (t ;; easier code because we're not bounded by MAXIMUM, but ;; basically the same (flet ((greedy-aux (start-pos) (declare (fixnum start-pos) (function repeat-matcher)) (let ((old-last-pos (svref *last-pos-stores* zero-length-num))) (when (and old-last-pos (= (the fixnum old-last-pos) start-pos)) (return-from greedy-aux (funcall next-fn start-pos))) (setf (svref *last-pos-stores* zero-length-num) start-pos) (or (prog1 (funcall repeat-matcher start-pos) (setf (svref *last-pos-stores* zero-length-num) old-last-pos)) (funcall next-fn start-pos))))) (setq repeat-matcher (create-matcher-aux (regex repetition) #'greedy-aux)) (lambda (start-pos) (declare (fixnum start-pos)) (setf (svref *last-pos-stores* zero-length-num) nil) (greedy-aux start-pos))))))) ;; code for non-greedy repetitions with minimum zero (defmacro non-greedy-constant-length-closure (check-curr-pos) "This is the template for simple non-greedy repetitions \(where simple means that the minimum number of repetitions is zero, that the inner regex to be checked is of fixed length LEN, and that it doesn't contain registers, i.e. there's no need for backtracking). CHECK-CURR-POS is a form which checks whether the inner regex of the repetition matches at CURR-POS." `(if maximum (lambda (start-pos) (declare (fixnum start-pos maximum)) ;; because we know LEN we know in advance where to stop at the ;; latest; we also take into consideration MIN-REST, i.e. the ;; minimal length of the part behind the repetition (let ((target-end-pos (min (1+ (- *end-pos* len min-rest)) (+ start-pos (the fixnum (* len maximum)))))) ;; move forward by LEN and always try NEXT-FN first, then ;; CHECK-CUR-POS (loop for curr-pos of-type fixnum from start-pos below target-end-pos by len thereis (funcall next-fn curr-pos) while ,check-curr-pos finally (return (funcall next-fn curr-pos))))) ;; basically the same code; it's just a bit easier because we're ;; not bounded by MAXIMUM (lambda (start-pos) (declare (fixnum start-pos)) (let ((target-end-pos (1+ (- *end-pos* len min-rest)))) (loop for curr-pos of-type fixnum from start-pos below target-end-pos by len thereis (funcall next-fn curr-pos) while ,check-curr-pos finally (return (funcall next-fn curr-pos))))))) (defgeneric create-non-greedy-constant-length-matcher (repetition next-fn) (declare #.*standard-optimize-settings*) (:documentation "Creates a closure which tries to match REPETITION. It is assumed that REPETITION is non-greedy and the minimal number of repetitions is zero. It is furthermore assumed that the inner regex of REPETITION is of fixed length and doesn't contain registers.")) (defmethod create-non-greedy-constant-length-matcher ((repetition repetition) next-fn) (declare #.*standard-optimize-settings*) (let ((len (len repetition)) (maximum (maximum repetition)) (regex (regex repetition)) (min-rest (min-rest repetition))) (declare (fixnum len min-rest) (function next-fn)) (cond ((zerop len) ;; inner regex has zero-length, so we can discard it ;; completely next-fn) (t ;; now first try to optimize for a couple of common cases (typecase regex (str (let ((str (str regex))) (if (= 1 len) ;; a single character (let ((chr (schar str 0))) (if (case-insensitive-p regex) (non-greedy-constant-length-closure (char-equal chr (schar *string* curr-pos))) (non-greedy-constant-length-closure (char= chr (schar *string* curr-pos))))) ;; a string (if (case-insensitive-p regex) (non-greedy-constant-length-closure (*string*-equal str curr-pos (+ curr-pos len) 0 len)) (non-greedy-constant-length-closure (*string*= str curr-pos (+ curr-pos len) 0 len)))))) (char-class ;; a character class (insert-char-class-tester (regex (schar *string* curr-pos)) (non-greedy-constant-length-closure (char-class-test)))) (everything (if (single-line-p regex) ;; a dot which really can match everything; we rely ;; on the compiler to optimize this away (non-greedy-constant-length-closure t) ;; a dot which has to watch out for #\Newline (non-greedy-constant-length-closure (char/= #\Newline (schar *string* curr-pos))))) (t ;; the general case - we build an inner matcher which ;; just checks for immediate success, i.e. NEXT-FN is ;; #'IDENTITY (let ((inner-matcher (create-matcher-aux regex #'identity))) (declare (function inner-matcher)) (non-greedy-constant-length-closure (funcall inner-matcher curr-pos))))))))) (defgeneric create-non-greedy-no-zero-matcher (repetition next-fn) (declare #.*standard-optimize-settings*) (:documentation "Creates a closure which tries to match REPETITION. It is assumed that REPETITION is non-greedy and the minimal number of repetitions is zero. It is furthermore assumed that the inner regex of REPETITION can never match a zero-length string \(or instead the maximal number of repetitions is 1).")) (defmethod create-non-greedy-no-zero-matcher ((repetition repetition) next-fn) (declare #.*standard-optimize-settings*) (let ((maximum (maximum repetition)) ;; REPEAT-MATCHER is part of the closure's environment but it ;; can only be defined after NON-GREEDY-AUX is defined repeat-matcher) (declare (function next-fn)) (cond ((eql maximum 1) ;; this is essentially like the next case but with a known ;; MAXIMUM of 1 we can get away without a counter (setq repeat-matcher (create-matcher-aux (regex repetition) next-fn)) (lambda (start-pos) (declare (function repeat-matcher)) (or (funcall next-fn start-pos) (funcall repeat-matcher start-pos)))) (maximum ;; we make a reservation for our slot in *REPEAT-COUNTERS* ;; because we need to keep track whether we've reached MAXIMUM ;; repetitions (let ((rep-num (incf-after *rep-num*))) (flet ((non-greedy-aux (start-pos) ;; the actual matcher which first calls NEXT-FN and ;; on failure tries to match the inner regex of ;; REPETITION (if we haven't done so too often) (declare (fixnum start-pos maximum rep-num) (function repeat-matcher)) (or (funcall next-fn start-pos) (and (< (aref *repeat-counters* rep-num) maximum) (incf (aref *repeat-counters* rep-num)) ;; note that REPEAT-MATCHER will call ;; NON-GREEDY-AUX again recursively (prog1 (funcall repeat-matcher start-pos) (decf (aref *repeat-counters* rep-num))))))) ;; create a closure to match the inner regex and to ;; implement backtracking via NON-GREEDY-AUX (setq repeat-matcher (create-matcher-aux (regex repetition) #'non-greedy-aux)) ;; the closure we return is just a thin wrapper around ;; NON-GREEDY-AUX to initialize the repetition counter (lambda (start-pos) (declare (fixnum start-pos)) (setf (aref *repeat-counters* rep-num) 0) (non-greedy-aux start-pos))))) (t ;; easier code because we're not bounded by MAXIMUM, but ;; basically the same (flet ((non-greedy-aux (start-pos) (declare (fixnum start-pos) (function repeat-matcher)) (or (funcall next-fn start-pos) (funcall repeat-matcher start-pos)))) (setq repeat-matcher (create-matcher-aux (regex repetition) #'non-greedy-aux)) #'non-greedy-aux))))) (defgeneric create-non-greedy-matcher (repetition next-fn) (declare #.*standard-optimize-settings*) (:documentation "Creates a closure which tries to match REPETITION. It is assumed that REPETITION is non-greedy and the minimal number of repetitions is zero.")) (defmethod create-non-greedy-matcher ((repetition repetition) next-fn) (declare #.*standard-optimize-settings*) ;; we make a reservation for our slot in *LAST-POS-STORES* because ;; we have to watch out for endless loops as the inner regex might ;; match zero-length strings (let ((zero-length-num (incf-after *zero-length-num*)) (maximum (maximum repetition)) ;; REPEAT-MATCHER is part of the closure's environment but it ;; can only be defined after NON-GREEDY-AUX is defined repeat-matcher) (declare (fixnum zero-length-num) (function next-fn)) (cond (maximum ;; we make a reservation for our slot in *REPEAT-COUNTERS* ;; because we need to keep track whether we've reached MAXIMUM ;; repetitions (let ((rep-num (incf-after *rep-num*))) (flet ((non-greedy-aux (start-pos) ;; the actual matcher which first calls NEXT-FN and ;; on failure tries to match the inner regex of ;; REPETITION (if we haven't done so too often) (declare (fixnum start-pos maximum rep-num) (function repeat-matcher)) (let ((old-last-pos (svref *last-pos-stores* zero-length-num))) (when (and old-last-pos (= (the fixnum old-last-pos) start-pos)) ;; stop immediately if we've been here before, ;; i.e. if the last attempt matched a zero-length ;; string (return-from non-greedy-aux (funcall next-fn start-pos))) ;; otherwise remember this position for the next ;; repetition (setf (svref *last-pos-stores* zero-length-num) start-pos) (or (funcall next-fn start-pos) (and (< (aref *repeat-counters* rep-num) maximum) (incf (aref *repeat-counters* rep-num)) ;; note that REPEAT-MATCHER will call ;; NON-GREEDY-AUX again recursively (prog1 (funcall repeat-matcher start-pos) (decf (aref *repeat-counters* rep-num)) (setf (svref *last-pos-stores* zero-length-num) old-last-pos))))))) ;; create a closure to match the inner regex and to ;; implement backtracking via NON-GREEDY-AUX (setq repeat-matcher (create-matcher-aux (regex repetition) #'non-greedy-aux)) ;; the closure we return is just a thin wrapper around ;; NON-GREEDY-AUX to initialize the repetition counter and our ;; slot in *LAST-POS-STORES* (lambda (start-pos) (declare (fixnum start-pos)) (setf (aref *repeat-counters* rep-num) 0 (svref *last-pos-stores* zero-length-num) nil) (non-greedy-aux start-pos))))) (t ;; easier code because we're not bounded by MAXIMUM, but ;; basically the same (flet ((non-greedy-aux (start-pos) (declare (fixnum start-pos) (function repeat-matcher)) (let ((old-last-pos (svref *last-pos-stores* zero-length-num))) (when (and old-last-pos (= (the fixnum old-last-pos) start-pos)) (return-from non-greedy-aux (funcall next-fn start-pos))) (setf (svref *last-pos-stores* zero-length-num) start-pos) (or (funcall next-fn start-pos) (prog1 (funcall repeat-matcher start-pos) (setf (svref *last-pos-stores* zero-length-num) old-last-pos)))))) (setq repeat-matcher (create-matcher-aux (regex repetition) #'non-greedy-aux)) (lambda (start-pos) (declare (fixnum start-pos)) (setf (svref *last-pos-stores* zero-length-num) nil) (non-greedy-aux start-pos))))))) ;; code for constant repetitions, i.e. those with a fixed number of repetitions (defmacro constant-repetition-constant-length-closure (check-curr-pos) "This is the template for simple constant repetitions (where simple means that the inner regex to be checked is of fixed length LEN, and that it doesn't contain registers, i.e. there's no need for backtracking) and where constant means that MINIMUM is equal to MAXIMUM. CHECK-CURR-POS is a form which checks whether the inner regex of the repetition matches at CURR-POS." `(lambda (start-pos) (declare (fixnum start-pos)) (let ((target-end-pos (+ start-pos (the fixnum (* len repetitions))))) (declare (fixnum target-end-pos)) ;; first check if we won't go beyond the end of the string (and (>= *end-pos* target-end-pos) ;; then loop through all repetitions step by step (loop for curr-pos of-type fixnum from start-pos below target-end-pos by len always ,check-curr-pos) ;; finally call NEXT-FN if we made it that far (funcall next-fn target-end-pos))))) (defgeneric create-constant-repetition-constant-length-matcher (repetition next-fn) (declare #.*standard-optimize-settings*) (:documentation "Creates a closure which tries to match REPETITION. It is assumed that REPETITION has a constant number of repetitions. It is furthermore assumed that the inner regex of REPETITION is of fixed length and doesn't contain registers.")) (defmethod create-constant-repetition-constant-length-matcher ((repetition repetition) next-fn) (declare #.*standard-optimize-settings*) (let ((len (len repetition)) (repetitions (minimum repetition)) (regex (regex repetition))) (declare (fixnum len repetitions) (function next-fn)) (if (zerop len) ;; if the length is zero it suffices to try once (create-matcher-aux regex next-fn) ;; otherwise try to optimize for a couple of common cases (typecase regex (str (let ((str (str regex))) (if (= 1 len) ;; a single character (let ((chr (schar str 0))) (if (case-insensitive-p regex) (constant-repetition-constant-length-closure (and (char-equal chr (schar *string* curr-pos)) (1+ curr-pos))) (constant-repetition-constant-length-closure (and (char= chr (schar *string* curr-pos)) (1+ curr-pos))))) ;; a string (if (case-insensitive-p regex) (constant-repetition-constant-length-closure (let ((next-pos (+ curr-pos len))) (declare (fixnum next-pos)) (and (*string*-equal str curr-pos next-pos 0 len) next-pos))) (constant-repetition-constant-length-closure (let ((next-pos (+ curr-pos len))) (declare (fixnum next-pos)) (and (*string*= str curr-pos next-pos 0 len) next-pos))))))) (char-class ;; a character class (insert-char-class-tester (regex (schar *string* curr-pos)) (constant-repetition-constant-length-closure (and (char-class-test) (1+ curr-pos))))) (everything (if (single-line-p regex) ;; a dot which really matches everything - we just have to ;; advance the index into *STRING* accordingly and check ;; if we didn't go past the end (lambda (start-pos) (declare (fixnum start-pos)) (let ((next-pos (+ start-pos repetitions))) (declare (fixnum next-pos)) (and (<= next-pos *end-pos*) (funcall next-fn next-pos)))) ;; a dot which is not in single-line-mode - make sure we ;; don't match #\Newline (constant-repetition-constant-length-closure (and (char/= #\Newline (schar *string* curr-pos)) (1+ curr-pos))))) (t ;; the general case - we build an inner matcher which just ;; checks for immediate success, i.e. NEXT-FN is #'IDENTITY (let ((inner-matcher (create-matcher-aux regex #'identity))) (declare (function inner-matcher)) (constant-repetition-constant-length-closure (funcall inner-matcher curr-pos)))))))) (defgeneric create-constant-repetition-matcher (repetition next-fn) (declare #.*standard-optimize-settings*) (:documentation "Creates a closure which tries to match REPETITION. It is assumed that REPETITION has a constant number of repetitions.")) (defmethod create-constant-repetition-matcher ((repetition repetition) next-fn) (declare #.*standard-optimize-settings*) (let ((repetitions (minimum repetition)) ;; we make a reservation for our slot in *REPEAT-COUNTERS* ;; because we need to keep track of the number of repetitions (rep-num (incf-after *rep-num*)) ;; REPEAT-MATCHER is part of the closure's environment but it ;; can only be defined after NON-GREEDY-AUX is defined repeat-matcher) (declare (fixnum repetitions rep-num) (function next-fn)) (if (zerop (min-len repetition)) ;; we make a reservation for our slot in *LAST-POS-STORES* ;; because we have to watch out for needless loops as the inner ;; regex might match zero-length strings (let ((zero-length-num (incf-after *zero-length-num*))) (declare (fixnum zero-length-num)) (flet ((constant-aux (start-pos) ;; the actual matcher which first calls NEXT-FN and ;; on failure tries to match the inner regex of ;; REPETITION (if we haven't done so too often) (declare (fixnum start-pos) (function repeat-matcher)) (let ((old-last-pos (svref *last-pos-stores* zero-length-num))) (when (and old-last-pos (= (the fixnum old-last-pos) start-pos)) ;; if we've been here before we matched a ;; zero-length string the last time, so we can ;; just carry on because we will definitely be ;; able to do this again often enough (return-from constant-aux (funcall next-fn start-pos))) ;; otherwise remember this position for the next ;; repetition (setf (svref *last-pos-stores* zero-length-num) start-pos) (cond ((< (aref *repeat-counters* rep-num) repetitions) ;; not enough repetitions yet, try it again (incf (aref *repeat-counters* rep-num)) ;; note that REPEAT-MATCHER will call ;; CONSTANT-AUX again recursively (prog1 (funcall repeat-matcher start-pos) (decf (aref *repeat-counters* rep-num)) (setf (svref *last-pos-stores* zero-length-num) old-last-pos))) (t ;; we're done - call NEXT-FN (funcall next-fn start-pos)))))) ;; create a closure to match the inner regex and to ;; implement backtracking via CONSTANT-AUX (setq repeat-matcher (create-matcher-aux (regex repetition) #'constant-aux)) ;; the closure we return is just a thin wrapper around ;; CONSTANT-AUX to initialize the repetition counter (lambda (start-pos) (declare (fixnum start-pos)) (setf (aref *repeat-counters* rep-num) 0 (aref *last-pos-stores* zero-length-num) nil) (constant-aux start-pos)))) ;; easier code because we don't have to care about zero-length ;; matches but basically the same (flet ((constant-aux (start-pos) (declare (fixnum start-pos) (function repeat-matcher)) (cond ((< (aref *repeat-counters* rep-num) repetitions) (incf (aref *repeat-counters* rep-num)) (prog1 (funcall repeat-matcher start-pos) (decf (aref *repeat-counters* rep-num)))) (t (funcall next-fn start-pos))))) (setq repeat-matcher (create-matcher-aux (regex repetition) #'constant-aux)) (lambda (start-pos) (declare (fixnum start-pos)) (setf (aref *repeat-counters* rep-num) 0) (constant-aux start-pos)))))) ;; the actual CREATE-MATCHER-AUX method for REPETITION objects which ;; utilizes all the functions and macros defined above (defmethod create-matcher-aux ((repetition repetition) next-fn) (declare #.*standard-optimize-settings*) (with-slots (minimum maximum len min-len greedyp contains-register-p) repetition (cond ((and maximum (zerop maximum)) ;; this should have been optimized away by CONVERT but just ;; in case... (error "Got REPETITION with MAXIMUM 0 \(should not happen)")) ((and maximum (= minimum maximum 1)) ;; this should have been optimized away by CONVERT but just ;; in case... (error "Got REPETITION with MAXIMUM 1 and MINIMUM 1 \(should not happen)")) ((and (eql minimum maximum) len (not contains-register-p)) (create-constant-repetition-constant-length-matcher repetition next-fn)) ((eql minimum maximum) (create-constant-repetition-matcher repetition next-fn)) ((and greedyp len (not contains-register-p)) (create-greedy-constant-length-matcher repetition next-fn)) ((and greedyp (or (plusp min-len) (eql maximum 1))) (create-greedy-no-zero-matcher repetition next-fn)) (greedyp (create-greedy-matcher repetition next-fn)) ((and len (plusp len) (not contains-register-p)) (create-non-greedy-constant-length-matcher repetition next-fn)) ((or (plusp min-len) (eql maximum 1)) (create-non-greedy-no-zero-matcher repetition next-fn)) (t (create-non-greedy-matcher repetition next-fn))))) cl-ppcre-2.0.3/scanner.lisp0000644000175700010010000006303111254505513013765 0ustar ediNone;;; -*- Mode: LISP; Syntax: COMMON-LISP; Package: CL-PPCRE; Base: 10 -*- ;;; $Header: /usr/local/cvsrep/cl-ppcre/scanner.lisp,v 1.36 2009/09/17 19:17:31 edi Exp $ ;;; Here the scanner for the actual regex as well as utility scanners ;;; for the constant start and end strings are created. ;;; Copyright (c) 2002-2009, Dr. Edmund Weitz. All rights reserved. ;;; Redistribution and use in source and binary forms, with or without ;;; modification, are permitted provided that the following conditions ;;; are met: ;;; * Redistributions of source code must retain the above copyright ;;; notice, this list of conditions and the following disclaimer. ;;; * Redistributions in binary form must reproduce the above ;;; copyright notice, this list of conditions and the following ;;; disclaimer in the documentation and/or other materials ;;; provided with the distribution. ;;; THIS SOFTWARE IS PROVIDED BY THE AUTHOR 'AS IS' AND ANY EXPRESSED ;;; OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED ;;; WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ;;; ARE DISCLAIMED. IN NO EVENT SHALL THE AUTHOR BE LIABLE FOR ANY ;;; DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL ;;; DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE ;;; GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS ;;; INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, ;;; WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING ;;; NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE OF THIS ;;; SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. (in-package :cl-ppcre) (defmacro bmh-matcher-aux (&key case-insensitive-p) "Auxiliary macro used by CREATE-BMH-MATCHER." (let ((char-compare (if case-insensitive-p 'char-equal 'char=))) `(lambda (start-pos) (declare (fixnum start-pos)) (if (or (minusp start-pos) (> (the fixnum (+ start-pos m)) *end-pos*)) nil (loop named bmh-matcher for k of-type fixnum = (+ start-pos m -1) then (+ k (max 1 (aref skip (char-code (schar *string* k))))) while (< k *end-pos*) do (loop for j of-type fixnum downfrom (1- m) for i of-type fixnum downfrom k while (and (>= j 0) (,char-compare (schar *string* i) (schar pattern j))) finally (if (minusp j) (return-from bmh-matcher (1+ i))))))))) (defun create-bmh-matcher (pattern case-insensitive-p) "Returns a Boyer-Moore-Horspool matcher which searches the (special) simple-string *STRING* for the first occurence of the substring PATTERN. The search starts at the position START-POS within *STRING* and stops before *END-POS* is reached. Depending on the second argument the search is case-insensitive or not. If the special variable *USE-BMH-MATCHERS* is NIL, use the standard SEARCH function instead. \(BMH matchers are faster but need much more space.)" (declare #.*standard-optimize-settings*) ;; see for ;; details (unless *use-bmh-matchers* (let ((test (if case-insensitive-p #'char-equal #'char=))) (return-from create-bmh-matcher (lambda (start-pos) (declare (fixnum start-pos)) (and (not (minusp start-pos)) (search pattern *string* :start2 start-pos :end2 *end-pos* :test test)))))) (let* ((m (length pattern)) (skip (make-array *regex-char-code-limit* :element-type 'fixnum :initial-element m))) (declare (fixnum m)) (loop for k of-type fixnum below m if case-insensitive-p do (setf (aref skip (char-code (char-upcase (schar pattern k)))) (- m k 1) (aref skip (char-code (char-downcase (schar pattern k)))) (- m k 1)) else do (setf (aref skip (char-code (schar pattern k))) (- m k 1))) (if case-insensitive-p (bmh-matcher-aux :case-insensitive-p t) (bmh-matcher-aux)))) (defmacro char-searcher-aux (&key case-insensitive-p) "Auxiliary macro used by CREATE-CHAR-SEARCHER." (let ((char-compare (if case-insensitive-p 'char-equal 'char=))) `(lambda (start-pos) (declare (fixnum start-pos)) (and (not (minusp start-pos)) (loop for i of-type fixnum from start-pos below *end-pos* thereis (and (,char-compare (schar *string* i) chr) i)))))) (defun create-char-searcher (chr case-insensitive-p) "Returns a function which searches the (special) simple-string *STRING* for the first occurence of the character CHR. The search starts at the position START-POS within *STRING* and stops before *END-POS* is reached. Depending on the second argument the search is case-insensitive or not." (declare #.*standard-optimize-settings*) (if case-insensitive-p (char-searcher-aux :case-insensitive-p t) (char-searcher-aux))) (declaim (inline newline-skipper)) (defun newline-skipper (start-pos) "Finds the next occurence of a character in *STRING* which is behind a #\Newline." (declare #.*standard-optimize-settings*) (declare (fixnum start-pos)) ;; we can start with (1- START-POS) without testing for (PLUSP ;; START-POS) because we know we'll never call NEWLINE-SKIPPER on ;; the first iteration (loop for i of-type fixnum from (1- start-pos) below *end-pos* thereis (and (char= (schar *string* i) #\Newline) (1+ i)))) (defmacro insert-advance-fn (advance-fn) "Creates the actual closure returned by CREATE-SCANNER-AUX by replacing '(ADVANCE-FN-DEFINITION) with a suitable definition for ADVANCE-FN. This is a utility macro used by CREATE-SCANNER-AUX." (subst advance-fn '(advance-fn-definition) '(lambda (string start end) (block scan ;; initialize a couple of special variables used by the ;; matchers (see file specials.lisp) (let* ((*string* string) (*start-pos* start) (*end-pos* end) ;; we will search forward for END-STRING if this value ;; isn't at least as big as POS (see ADVANCE-FN), so it ;; is safe to start to the left of *START-POS*; note ;; that this value will _never_ be decremented - this ;; is crucial to the scanning process (*end-string-pos* (1- *start-pos*)) ;; the next five will shadow the variables defined by ;; DEFPARAMETER; at this point, we don't know if we'll ;; actually use them, though (*repeat-counters* *repeat-counters*) (*last-pos-stores* *last-pos-stores*) (*reg-starts* *reg-starts*) (*regs-maybe-start* *regs-maybe-start*) (*reg-ends* *reg-ends*) ;; we might be able to optimize the scanning process by ;; (virtually) shifting *START-POS* to the right (scan-start-pos *start-pos*) (starts-with-str (if start-string-test (str starts-with) nil)) ;; we don't need to try further than MAX-END-POS (max-end-pos (- *end-pos* min-len))) (declare (fixnum scan-start-pos) (function match-fn)) ;; definition of ADVANCE-FN will be inserted here by macrology (labels ((advance-fn-definition)) (declare (inline advance-fn)) (when (plusp rep-num) ;; we have at least one REPETITION which needs to count ;; the number of repetitions (setq *repeat-counters* (make-array rep-num :initial-element 0 :element-type 'fixnum))) (when (plusp zero-length-num) ;; we have at least one REPETITION which needs to watch ;; out for zero-length repetitions (setq *last-pos-stores* (make-array zero-length-num :initial-element nil))) (when (plusp reg-num) ;; we have registers in our regular expression (setq *reg-starts* (make-array reg-num :initial-element nil) *regs-maybe-start* (make-array reg-num :initial-element nil) *reg-ends* (make-array reg-num :initial-element nil))) (when end-anchored-p ;; the regular expression has a constant end string which ;; is anchored at the very end of the target string ;; (perhaps modulo a #\Newline) (let ((end-test-pos (- *end-pos* (the fixnum end-string-len)))) (declare (fixnum end-test-pos) (function end-string-test)) (unless (setq *end-string-pos* (funcall end-string-test end-test-pos)) (when (and (= 1 (the fixnum end-anchored-p)) (> *end-pos* scan-start-pos) (char= #\Newline (schar *string* (1- *end-pos*)))) ;; if we didn't find an end string candidate from ;; END-TEST-POS and if a #\Newline at the end is ;; allowed we try it again from one position to the ;; left (setq *end-string-pos* (funcall end-string-test (1- end-test-pos)))))) (unless (and *end-string-pos* (<= *start-pos* *end-string-pos*)) ;; no end string candidate found, so give up (return-from scan nil)) (when end-string-offset ;; if the offset of the constant end string from the ;; left of the regular expression is known we can start ;; scanning further to the right; this is similar to ;; what we might do in ADVANCE-FN (setq scan-start-pos (max scan-start-pos (- (the fixnum *end-string-pos*) (the fixnum end-string-offset)))))) (cond (start-anchored-p ;; we're anchored at the start of the target string, ;; so no need to try again after first failure (when (or (/= *start-pos* scan-start-pos) (< max-end-pos *start-pos*)) ;; if END-STRING-OFFSET has proven that we don't ;; need to bother to scan from *START-POS* or if the ;; minimal length of the regular expression is ;; longer than the target string we give up (return-from scan nil)) (when starts-with-str (locally (declare (fixnum starts-with-len)) (cond ((and (case-insensitive-p starts-with) (not (*string*-equal starts-with-str *start-pos* (+ *start-pos* starts-with-len) 0 starts-with-len))) ;; the regular expression has a ;; case-insensitive constant start string ;; and we didn't find it (return-from scan nil)) ((and (not (case-insensitive-p starts-with)) (not (*string*= starts-with-str *start-pos* (+ *start-pos* starts-with-len) 0 starts-with-len))) ;; the regular expression has a ;; case-sensitive constant start string ;; and we didn't find it (return-from scan nil)) (t nil)))) (when (and end-string-test (not end-anchored-p)) ;; the regular expression has a constant end string ;; which isn't anchored so we didn't check for it ;; already (block end-string-loop ;; we temporarily use *END-STRING-POS* as our ;; starting position to look for end string ;; candidates (setq *end-string-pos* *start-pos*) (loop (unless (setq *end-string-pos* (funcall (the function end-string-test) *end-string-pos*)) ;; no end string candidate found, so give up (return-from scan nil)) (unless end-string-offset ;; end string doesn't have an offset so we ;; can start scanning now (return-from end-string-loop)) (let ((maybe-start-pos (- (the fixnum *end-string-pos*) (the fixnum end-string-offset)))) (cond ((= maybe-start-pos *start-pos*) ;; offset of end string into regular ;; expression matches start anchor - ;; fine... (return-from end-string-loop)) ((and (< maybe-start-pos *start-pos*) (< (+ *end-string-pos* end-string-len) *end-pos*)) ;; no match but maybe we find another ;; one to the right - try again (incf *end-string-pos*)) (t ;; otherwise give up (return-from scan nil))))))) ;; if we got here we scan exactly once (let ((next-pos (funcall match-fn *start-pos*))) (when next-pos (values (if next-pos *start-pos* nil) next-pos *reg-starts* *reg-ends*)))) (t (loop for pos = (if starts-with-everything ;; don't jump to the next ;; #\Newline on the first ;; iteration scan-start-pos (advance-fn scan-start-pos)) then (advance-fn pos) ;; give up if the regular expression can't fit ;; into the rest of the target string while (and pos (<= (the fixnum pos) max-end-pos)) do (let ((next-pos (funcall match-fn pos))) (when next-pos (return-from scan (values pos next-pos *reg-starts* *reg-ends*))) ;; not yet found, increment POS #-cormanlisp (incf (the fixnum pos)) #+cormanlisp (incf pos))))))))) :test #'equalp)) (defun create-scanner-aux (match-fn min-len start-anchored-p starts-with start-string-test end-anchored-p end-string-test end-string-len end-string-offset rep-num zero-length-num reg-num) "Auxiliary function to create and return a scanner \(which is actually a closure). Used by CREATE-SCANNER." (declare #.*standard-optimize-settings*) (declare (fixnum min-len zero-length-num rep-num reg-num)) (let ((starts-with-len (if (typep starts-with 'str) (len starts-with))) (starts-with-everything (typep starts-with 'everything))) (cond ;; this COND statement dispatches on the different versions we ;; have for ADVANCE-FN and creates different closures for each; ;; note that you see only the bodies of ADVANCE-FN below - the ;; actual scanner is defined in INSERT-ADVANCE-FN above; (we ;; could have done this with closures instead of macrology but ;; would have consed a lot more) ((and start-string-test end-string-test end-string-offset) ;; we know that the regular expression has constant start and ;; end strings and we know the end string's offset (from the ;; left) (insert-advance-fn (advance-fn (pos) (declare (fixnum end-string-offset starts-with-len) (function start-string-test end-string-test)) (loop (unless (setq pos (funcall start-string-test pos)) ;; give up completely if we can't find a start string ;; candidate (return-from scan nil)) (locally ;; from here we know that POS is a FIXNUM (declare (fixnum pos)) (when (= pos (- (the fixnum *end-string-pos*) end-string-offset)) ;; if we already found an end string candidate the ;; position of which matches the start string ;; candidate we're done (return-from advance-fn pos)) (let ((try-pos (+ pos starts-with-len))) ;; otherwise try (again) to find an end string ;; candidate which starts behind the start string ;; candidate (loop (unless (setq *end-string-pos* (funcall end-string-test try-pos)) ;; no end string candidate found, so give up (return-from scan nil)) ;; NEW-POS is where we should start scanning ;; according to the end string candidate (let ((new-pos (- (the fixnum *end-string-pos*) end-string-offset))) (declare (fixnum new-pos *end-string-pos*)) (cond ((= new-pos pos) ;; if POS and NEW-POS are equal then the ;; two candidates agree so we're fine (return-from advance-fn pos)) ((> new-pos pos) ;; if NEW-POS is further to the right we ;; advance POS and try again, i.e. we go ;; back to the start of the outer LOOP (setq pos new-pos) ;; this means "return from inner LOOP" (return)) (t ;; otherwise NEW-POS is smaller than POS, ;; so we have to redo the inner LOOP to ;; find another end string candidate ;; further to the right (setq try-pos (1+ *end-string-pos*)))))))))))) ((and starts-with-everything end-string-test end-string-offset) ;; we know that the regular expression starts with ".*" (which ;; is not in single-line-mode, see CREATE-SCANNER-AUX) and ends ;; with a constant end string and we know the end string's ;; offset (from the left) (insert-advance-fn (advance-fn (pos) (declare (fixnum end-string-offset) (function end-string-test)) (loop (unless (setq pos (newline-skipper pos)) ;; if we can't find a #\Newline we give up immediately (return-from scan nil)) (locally ;; from here we know that POS is a FIXNUM (declare (fixnum pos)) (when (= pos (- (the fixnum *end-string-pos*) end-string-offset)) ;; if we already found an end string candidate the ;; position of which matches the place behind the ;; #\Newline we're done (return-from advance-fn pos)) (let ((try-pos pos)) ;; otherwise try (again) to find an end string ;; candidate which starts behind the #\Newline (loop (unless (setq *end-string-pos* (funcall end-string-test try-pos)) ;; no end string candidate found, so we give up (return-from scan nil)) ;; NEW-POS is where we should start scanning ;; according to the end string candidate (let ((new-pos (- (the fixnum *end-string-pos*) end-string-offset))) (declare (fixnum new-pos *end-string-pos*)) (cond ((= new-pos pos) ;; if POS and NEW-POS are equal then the ;; the end string candidate agrees with ;; the #\Newline so we're fine (return-from advance-fn pos)) ((> new-pos pos) ;; if NEW-POS is further to the right we ;; advance POS and try again, i.e. we go ;; back to the start of the outer LOOP (setq pos new-pos) ;; this means "return from inner LOOP" (return)) (t ;; otherwise NEW-POS is smaller than POS, ;; so we have to redo the inner LOOP to ;; find another end string candidate ;; further to the right (setq try-pos (1+ *end-string-pos*)))))))))))) ((and start-string-test end-string-test) ;; we know that the regular expression has constant start and ;; end strings; similar to the first case but we only need to ;; check for the end string, it doesn't provide enough ;; information to advance POS (insert-advance-fn (advance-fn (pos) (declare (function start-string-test end-string-test)) (unless (setq pos (funcall start-string-test pos)) (return-from scan nil)) (if (<= (the fixnum pos) (the fixnum *end-string-pos*)) (return-from advance-fn pos)) (unless (setq *end-string-pos* (funcall end-string-test pos)) (return-from scan nil)) pos))) ((and starts-with-everything end-string-test) ;; we know that the regular expression starts with ".*" (which ;; is not in single-line-mode, see CREATE-SCANNER-AUX) and ends ;; with a constant end string; similar to the second case but we ;; only need to check for the end string, it doesn't provide ;; enough information to advance POS (insert-advance-fn (advance-fn (pos) (declare (function end-string-test)) (unless (setq pos (newline-skipper pos)) (return-from scan nil)) (if (<= (the fixnum pos) (the fixnum *end-string-pos*)) (return-from advance-fn pos)) (unless (setq *end-string-pos* (funcall end-string-test pos)) (return-from scan nil)) pos))) (start-string-test ;; just check for constant start string candidate (insert-advance-fn (advance-fn (pos) (declare (function start-string-test)) (unless (setq pos (funcall start-string-test pos)) (return-from scan nil)) pos))) (starts-with-everything ;; just advance POS with NEWLINE-SKIPPER (insert-advance-fn (advance-fn (pos) (unless (setq pos (newline-skipper pos)) (return-from scan nil)) pos))) (end-string-test ;; just check for the next end string candidate if POS has ;; advanced beyond the last one (insert-advance-fn (advance-fn (pos) (declare (function end-string-test)) (if (<= (the fixnum pos) (the fixnum *end-string-pos*)) (return-from advance-fn pos)) (unless (setq *end-string-pos* (funcall end-string-test pos)) (return-from scan nil)) pos))) (t ;; not enough optimization information about the regular ;; expression to optimize so we just return POS (insert-advance-fn (advance-fn (pos) pos)))))) cl-ppcre-2.0.3/specials.lisp0000644000175700010010000001453311271772157014153 0ustar ediNone;;; -*- Mode: LISP; Syntax: COMMON-LISP; Package: CL-PPCRE; Base: 10 -*- ;;; $Header: /usr/local/cvsrep/cl-ppcre/specials.lisp,v 1.43 2009/10/28 07:36:15 edi Exp $ ;;; globally declared special variables ;;; Copyright (c) 2002-2009, Dr. Edmund Weitz. All rights reserved. ;;; Redistribution and use in source and binary forms, with or without ;;; modification, are permitted provided that the following conditions ;;; are met: ;;; * Redistributions of source code must retain the above copyright ;;; notice, this list of conditions and the following disclaimer. ;;; * Redistributions in binary form must reproduce the above ;;; copyright notice, this list of conditions and the following ;;; disclaimer in the documentation and/or other materials ;;; provided with the distribution. ;;; THIS SOFTWARE IS PROVIDED BY THE AUTHOR 'AS IS' AND ANY EXPRESSED ;;; OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED ;;; WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ;;; ARE DISCLAIMED. IN NO EVENT SHALL THE AUTHOR BE LIABLE FOR ANY ;;; DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL ;;; DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE ;;; GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS ;;; INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, ;;; WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING ;;; NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE OF THIS ;;; SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. (in-package :cl-ppcre) ;;; special variables used to effect declarations (defvar *standard-optimize-settings* '(optimize speed (safety 0) (space 0) (debug 1) (compilation-speed 0) #+:lispworks (hcl:fixnum-safety 0)) "The standard optimize settings used by most declaration expressions.") (defvar *special-optimize-settings* '(optimize speed space) "Special optimize settings used only by a few declaration expressions.") ;;; special variables used by the lexer/parser combo (defvar *extended-mode-p* nil "Whether the parser will start in extended mode.") (declaim (boolean *extended-mode-p*)) ;;; special variables used by the SCAN function and the matchers (defvar *regex-char-code-limit* char-code-limit "The upper exclusive bound on the char-codes of characters which can occur in character classes. Change this value BEFORE creating scanners if you don't need the \(full) Unicode support of implementations like AllegroCL, CLISP, LispWorks, or SBCL.") (declaim (fixnum *regex-char-code-limit*)) (defvar *string* "" "The string which is currently scanned by SCAN. Will always be coerced to a SIMPLE-STRING.") #+:lispworks (declaim (lw:simple-text-string *string*)) #-:lispworks (declaim (simple-string *string*)) (defvar *start-pos* 0 "Where to start scanning within *STRING*.") (declaim (fixnum *start-pos*)) (defvar *real-start-pos* nil "The real start of *STRING*. This is for repeated scans and is only used internally.") (declaim (type (or null fixnum) *real-start-pos*)) (defvar *end-pos* 0 "Where to stop scanning within *STRING*.") (declaim (fixnum *end-pos*)) (defvar *reg-starts* (make-array 0) "An array which holds the start positions of the current register candidates.") (declaim (simple-vector *reg-starts*)) (defvar *regs-maybe-start* (make-array 0) "An array which holds the next start positions of the current register candidates.") (declaim (simple-vector *regs-maybe-start*)) (defvar *reg-ends* (make-array 0) "An array which holds the end positions of the current register candidates.") (declaim (simple-vector *reg-ends*)) (defvar *end-string-pos* nil "Start of the next possible end-string candidate.") (defvar *rep-num* 0 "Counts the number of \"complicated\" repetitions while the matchers are built.") (declaim (fixnum *rep-num*)) (defvar *zero-length-num* 0 "Counts the number of repetitions the inner regexes of which may have zero-length while the matchers are built.") (declaim (fixnum *zero-length-num*)) (defvar *repeat-counters* (make-array 0 :initial-element 0 :element-type 'fixnum) "An array to keep track of how often repetitive patterns have been tested already.") (declaim (type (array fixnum (*)) *repeat-counters*)) (defvar *last-pos-stores* (make-array 0) "An array to keep track of the last positions where we saw repetitive patterns. Only used for patterns which might have zero length.") (declaim (simple-vector *last-pos-stores*)) (defvar *use-bmh-matchers* nil "Whether the scanners created by CREATE-SCANNER should use the \(fast but large) Boyer-Moore-Horspool matchers.") (defvar *optimize-char-classes* nil "Whether character classes should be compiled into look-ups into O\(1) data structures. This is usually fast but will be costly in terms of scanner creation time and might be costly in terms of size if *REGEX-CHAR-CODE-LIMIT* is high. This value will be used as the :KIND keyword argument to CREATE-OPTIMIZED-TEST-FUNCTION - see there for the possible non-NIL values.") (defvar *property-resolver* nil "Should be NIL or a designator for a function which accepts strings and returns unary character test functions or NIL. This 'resolver' is intended to handle `character properties' like \\p{IsAlpha}. If *PROPERTY-RESOLVER* is NIL, then the parser will simply treat \\p and \\P as #\\p and #\\P as in older versions of CL-PPCRE.") (defvar *allow-quoting* nil "Whether the parser should support Perl's \\Q and \\E.") (defvar *allow-named-registers* nil "Whether the parser should support AllegroCL's named registers \(?\"\") and back-reference \\k syntax.") (pushnew :cl-ppcre *features*) ;; stuff for Nikodemus Siivola's HYPERDOC ;; see ;; and ;; also used by LW-ADD-ONS (defvar *hyperdoc-base-uri* "http://weitz.de/cl-ppcre/") (let ((exported-symbols-alist (loop for symbol being the external-symbols of :cl-ppcre collect (cons symbol (concatenate 'string "#" (string-downcase symbol)))))) (defun hyperdoc-lookup (symbol type) (declare (ignore type)) (cdr (assoc symbol exported-symbols-alist :test #'eq)))) cl-ppcre-2.0.3/test/0000755000175700010010000000000011271772245012426 5ustar ediNonecl-ppcre-2.0.3/test/packages.lisp0000644000175700010010000000346611254505520015075 0ustar ediNone;;; -*- Mode: LISP; Syntax: COMMON-LISP; Package: CL-USER; Base: 10 -*- ;;; $Header: /usr/local/cvsrep/cl-ppcre/test/packages.lisp,v 1.4 2009/09/17 19:17:36 edi Exp $ ;;; Copyright (c) 2002-2009, Dr. Edmund Weitz. All rights reserved. ;;; Redistribution and use in source and binary forms, with or without ;;; modification, are permitted provided that the following conditions ;;; are met: ;;; * Redistributions of source code must retain the above copyright ;;; notice, this list of conditions and the following disclaimer. ;;; * Redistributions in binary form must reproduce the above ;;; copyright notice, this list of conditions and the following ;;; disclaimer in the documentation and/or other materials ;;; provided with the distribution. ;;; THIS SOFTWARE IS PROVIDED BY THE AUTHOR 'AS IS' AND ANY EXPRESSED ;;; OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED ;;; WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ;;; ARE DISCLAIMED. IN NO EVENT SHALL THE AUTHOR BE LIABLE FOR ANY ;;; DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL ;;; DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE ;;; GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS ;;; INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, ;;; WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING ;;; NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE OF THIS ;;; SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. (in-package :cl-user) (defpackage :cl-ppcre-test #+genera (:shadowing-import-from :common-lisp :lambda) (:use #-:genera :cl #+:genera :future-common-lisp :cl-ppcre) (:import-from :cl-ppcre :*standard-optimize-settings* :string-list-to-simple-string) (:export :run-all-tests :unicode-test)) cl-ppcre-2.0.3/test/perl-tests.lisp0000644000175700010010000002022311254505520015407 0ustar ediNone;;; -*- Mode: LISP; Syntax: COMMON-LISP; Package: CL-PPCRE-TEST; Base: 10 -*- ;;; $Header: /usr/local/cvsrep/cl-ppcre/test/perl-tests.lisp,v 1.8 2009/09/17 19:17:36 edi Exp $ ;;; The tests in this file test CL-PPCRE against testdata generated by ;;; the Perl program `perltest.pl' from the input file `testinput' in ;;; order to check compatibility with Perl and correctness of the ;;; regex engine. ;;; Copyright (c) 2002-2009, Dr. Edmund Weitz. All rights reserved. ;;; Redistribution and use in source and binary forms, with or without ;;; modification, are permitted provided that the following conditions ;;; are met: ;;; * Redistributions of source code must retain the above copyright ;;; notice, this list of conditions and the following disclaimer. ;;; * Redistributions in binary form must reproduce the above ;;; copyright notice, this list of conditions and the following ;;; disclaimer in the documentation and/or other materials ;;; provided with the distribution. ;;; THIS SOFTWARE IS PROVIDED BY THE AUTHOR 'AS IS' AND ANY EXPRESSED ;;; OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED ;;; WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ;;; ARE DISCLAIMED. IN NO EVENT SHALL THE AUTHOR BE LIABLE FOR ANY ;;; DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL ;;; DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE ;;; GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS ;;; INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, ;;; WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING ;;; NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE OF THIS ;;; SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. (in-package :cl-ppcre-test) (defvar *tests-to-skip* '(662 790 1439) "Some tests we skip because the testdata is generated by a Perl program and CL-PPCRE differs from Perl for these tests - on purpose.") (defun create-string-from-input (input) "Converts INPUT to a string which can be used in TEST below. The input file `testdata' encodes strings containing non-printable characters as lists where those characters are represented by their character code." (etypecase input ((or null string) input) (list (string-list-to-simple-string (loop for element in input if (stringp element) collect element else collect (string (code-char element))))))) (defun perl-test (&key (file-name (make-pathname :name "perltestdata" :type nil :version nil :defaults *this-file*) file-name-provided-p) (external-format '(:latin-1 :eol-style :lf)) verbose) "Loops through all test cases in FILE-NAME and prints a report if VERBOSE is true. EXTERNAL-FORMAT is the FLEXI-STREAMS external format which is used to read the file. Returns a true value if all tests succeeded. For the syntax of the tests in FILE-NAME refer to the source code of this function and to the Perl script perltest.pl which generates such test files." (declare #.*standard-optimize-settings*) (with-open-file (binary-stream file-name :element-type 'flex:octet) (let ((stream (flex:make-flexi-stream binary-stream :external-format external-format)) ;; the standard Perl tests don't need full Unicode support (*regex-char-code-limit* (if file-name-provided-p *regex-char-code-limit* 256)) ;; we need this for the standard test suite or otherwise we ;; might get stack overflows (*optimize-char-classes* (if file-name-provided-p *optimize-char-classes* :charmap)) ;; we only check for correctness and don't care about speed ;; that match (but rather about space constraints of the ;; trial versions) (*use-bmh-matchers* (if file-name-provided-p *use-bmh-matchers* nil)) ;; some tests in the Perl suite explicitly check for this (*allow-quoting* (if file-name-provided-p *allow-quoting* t))) (do-tests ((format nil "Running tests in file ~S" (file-namestring file-name)) (not verbose)) (let ((input-line (or (read stream nil) (done))) errors) (destructuring-bind (counter info-string% regex% case-insensitive-mode multi-line-mode single-line-mode extended-mode target% perl-error expected-result% expected-registers) input-line (destructuring-bind (info-string regex target expected-result) (mapcar 'create-string-from-input (list info-string% regex% target% expected-result%)) (setq expected-registers (mapcar 'create-string-from-input expected-registers)) (unless (find counter *tests-to-skip* :test #'=) (when verbose (format t "~&~4D: ~S" counter info-string)) (let ((scanner (handler-bind ((error (lambda (condition) (declare (ignore condition)) (when perl-error ;; we expected an ;; error, so we can ;; signal success (return-from test-block))))) (create-scanner regex :case-insensitive-mode case-insensitive-mode :multi-line-mode multi-line-mode :single-line-mode single-line-mode :extended-mode extended-mode)))) (block test-block (multiple-value-bind (start end reg-starts reg-ends) (scan scanner target) (cond (perl-error (push (format nil "expected an error but got a result.") errors)) (t (when (not (eq start expected-result)) (if start (let ((result (subseq target start end))) (unless (string= result expected-result) (push (format nil "expected ~S but got ~S." expected-result result) errors)) (setq reg-starts (coerce reg-starts 'list) reg-ends (coerce reg-ends 'list)) (loop for i from 0 for expected-register in expected-registers for reg-start = (nth i reg-starts) for reg-end = (nth i reg-ends) for register = (if (and reg-start reg-end) (subseq target reg-start reg-end) nil) unless (string= expected-register register) do (push (format nil "\\~A: expected ~S but got ~S." (1+ i) expected-register register) errors))) (push (format nil "expected ~S but got ~S." expected-result start) errors)))))) errors)))))))))) cl-ppcre-2.0.3/test/perltest.pl0000755000175700010010000000642111034234027014617 0ustar ediNone#!/usr/bin/perl # $Header: /usr/local/cvsrep/cl-ppcre/test/perltest.pl,v 1.1 2008/07/06 21:24:39 edi Exp $ # This is a heavily modified version of the file 'perltest' which # comes with the PCRE library package, which is open source software, # written by Philip Hazel, and copyright by the University of # Cambridge, England. # The PCRE library package is available from # sub string_for_lisp { my(@a, $t, $in_string, $switch); my $string = shift; $string =~ s/\\/\\\\/g; $string =~ s/"/\\"/g; return "\"$string\"" if $string =~ /^[\n\x20-\x7f]*$/; $in_string = 1; foreach $c (split(//, $string)) { if (ord $c >= 32 and ord $c < 127) { if ($in_string) { $t .= $c; } else { $in_string = 1; $t = $c; } } else { if ($in_string) { push @a, "\"$t\""; $in_string = 0; $switch = 1; } push @a, ord $c; } } if ($switch) { if ($in_string) { push @a, "\"$t\""; } '(' . (join ' ', @a) . ')'; } else { "\"$t\""; } } NEXT_RE: while (1) { last if !($_ = <>); next if $_ eq ""; $pattern = $_; while ($pattern !~ /^\s*(.).*\1/s) { last if !($_ = <>); $pattern .= $_; } chomp($pattern); $pattern =~ s/\s+$//; $pattern =~ s/\+(?=[a-z]*$)//; $multi_line_mode = ($pattern =~ /m[a-z]*$/) ? 't' : 'nil'; $single_line_mode = ($pattern =~ /s[a-z]*$/) ? 't' : 'nil'; $extended_mode = ($pattern =~ /x[a-z]*$/) ? 't' : 'nil'; $case_insensitive_mode = ($pattern =~ /i[a-z]*$/) ? 't' : 'nil'; $pattern =~ s/^(.*)g([a-z]*)$/\1\2/; $pattern_for_lisp = $pattern; $pattern_for_lisp =~ s/[a-z]*$//; $pattern_for_lisp =~ s/^\s*(.)(.*)\1/$2/s; $pattern_for_lisp =~ s/\\/\\\\/g; $pattern_for_lisp =~ s/"/\\"/g; $pattern = "/(?#)/$2" if ($pattern =~ /^(.)\1(.*)$/); while (1) { last NEXT_RE if !($_ = <>); chomp; s/\s+$//; s/^\s+//; last if ($_ eq ""); $info_string = string_for_lisp "\"$_\" =~ $pattern"; $x = eval "\"$_\""; @subs = (); eval <<"END"; if (\$x =~ ${pattern}) { push \@subs,\$&; push \@subs,\$1; push \@subs,\$2; push \@subs,\$3; push \@subs,\$4; push \@subs,\$5; push \@subs,\$6; push \@subs,\$7; push \@subs,\$8; push \@subs,\$9; push \@subs,\$10; push \@subs,\$11; push \@subs,\$12; push \@subs,\$13; push \@subs,\$14; push \@subs,\$15; push \@subs,\$16; } \$test = sub { my \$times = shift; my \$start = time; for (my \$i = 0; \$i < \$times; \$i++) { \$x =~ ${pattern}; } return time - \$start; }; END $counter++; print STDERR "$counter\n"; if ($@) { $error = 't'; } else { $error = 'nil'; } print "($counter $info_string \"$pattern_for_lisp\" $case_insensitive_mode $multi_line_mode $single_line_mode $extended_mode " . string_for_lisp($x) . " $error "; if (!@subs) { print 'nil nil'; } else { print string_for_lisp($subs[0]) . ' ('; undef $not_first; for ($i = 1; $i <= 16; $i++) { print ' ' unless $i == 1; if (defined $subs[$i]) { print string_for_lisp $subs[$i]; } else { print 'nil'; } } print ')'; } print ")\n"; } } cl-ppcre-2.0.3/test/perltestdata0000644000175700010010000321722111041362031015034 0ustar ediNone(1 "\"the quick brown fox\" =~ /the quick brown fox/" "the quick brown fox" nil nil nil nil "the quick brown fox" nil "the quick brown fox" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (2 "\"The quick brown FOX\" =~ /the quick brown fox/" "the quick brown fox" nil nil nil nil "The quick brown FOX" nil nil nil) (3 "\"What do you know about the quick brown fox?\" =~ /the quick brown fox/" "the quick brown fox" nil nil nil nil "What do you know about the quick brown fox?" nil "the quick brown fox" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (4 "\"What do you know about THE QUICK BROWN FOX?\" =~ /the quick brown fox/" "the quick brown fox" nil nil nil nil "What do you know about THE QUICK BROWN FOX?" nil nil nil) (5 "\"the quick brown fox\" =~ /The quick brown fox/i" "The quick brown fox" t nil nil nil "the quick brown fox" nil "the quick brown fox" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (6 "\"The quick brown FOX\" =~ /The quick brown fox/i" "The quick brown fox" t nil nil nil "The quick brown FOX" nil "The quick brown FOX" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (7 "\"What do you know about the quick brown fox?\" =~ /The quick brown fox/i" "The quick brown fox" t nil nil nil "What do you know about the quick brown fox?" nil "the quick brown fox" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (8 "\"What do you know about THE QUICK BROWN FOX?\" =~ /The quick brown fox/i" "The quick brown fox" t nil nil nil "What do you know about THE QUICK BROWN FOX?" nil "THE QUICK BROWN FOX" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (9 "\"abcd\\t\\n\\r\\f\\a\\e9;\\$\\\\?caxyz\" =~ /abcd\\t\\n\\r\\f\\a\\e\\071\\x3b\\$\\\\\\?caxyz/" "abcd\\t\\n\\r\\f\\a\\e\\071\\x3b\\$\\\\\\?caxyz" nil nil nil nil ("abcd" 9 10 13 12 7 27 "9;$\\?caxyz") nil ("abcd" 9 10 13 12 7 27 "9;$\\?caxyz") (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (10 "\"abxyzpqrrrabbxyyyypqAzz\" =~ /a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz/" "a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz" nil nil nil nil "abxyzpqrrrabbxyyyypqAzz" nil "abxyzpqrrrabbxyyyypqAzz" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (11 "\"abxyzpqrrrabbxyyyypqAzz\" =~ /a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz/" "a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz" nil nil nil nil "abxyzpqrrrabbxyyyypqAzz" nil "abxyzpqrrrabbxyyyypqAzz" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (12 "\"aabxyzpqrrrabbxyyyypqAzz\" =~ /a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz/" "a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz" nil nil nil nil "aabxyzpqrrrabbxyyyypqAzz" nil "aabxyzpqrrrabbxyyyypqAzz" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (13 "\"aaabxyzpqrrrabbxyyyypqAzz\" =~ /a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz/" "a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz" nil nil nil nil "aaabxyzpqrrrabbxyyyypqAzz" nil "aaabxyzpqrrrabbxyyyypqAzz" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (14 "\"aaaabxyzpqrrrabbxyyyypqAzz\" =~ /a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz/" "a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz" nil nil nil nil "aaaabxyzpqrrrabbxyyyypqAzz" nil "aaaabxyzpqrrrabbxyyyypqAzz" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (15 "\"abcxyzpqrrrabbxyyyypqAzz\" =~ /a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz/" "a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz" nil nil nil nil "abcxyzpqrrrabbxyyyypqAzz" nil "abcxyzpqrrrabbxyyyypqAzz" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (16 "\"aabcxyzpqrrrabbxyyyypqAzz\" =~ /a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz/" "a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz" nil nil nil nil "aabcxyzpqrrrabbxyyyypqAzz" nil "aabcxyzpqrrrabbxyyyypqAzz" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (17 "\"aaabcxyzpqrrrabbxyyyypAzz\" =~ /a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz/" "a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz" nil nil nil nil "aaabcxyzpqrrrabbxyyyypAzz" nil "aaabcxyzpqrrrabbxyyyypAzz" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (18 "\"aaabcxyzpqrrrabbxyyyypqAzz\" =~ /a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz/" "a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz" nil nil nil nil "aaabcxyzpqrrrabbxyyyypqAzz" nil "aaabcxyzpqrrrabbxyyyypqAzz" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (19 "\"aaabcxyzpqrrrabbxyyyypqqAzz\" =~ /a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz/" "a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz" nil nil nil nil "aaabcxyzpqrrrabbxyyyypqqAzz" nil "aaabcxyzpqrrrabbxyyyypqqAzz" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (20 "\"aaabcxyzpqrrrabbxyyyypqqqAzz\" =~ /a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz/" "a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz" nil nil nil nil "aaabcxyzpqrrrabbxyyyypqqqAzz" nil "aaabcxyzpqrrrabbxyyyypqqqAzz" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (21 "\"aaabcxyzpqrrrabbxyyyypqqqqAzz\" =~ /a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz/" "a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz" nil nil nil nil "aaabcxyzpqrrrabbxyyyypqqqqAzz" nil "aaabcxyzpqrrrabbxyyyypqqqqAzz" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (22 "\"aaabcxyzpqrrrabbxyyyypqqqqqAzz\" =~ /a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz/" "a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz" nil nil nil nil "aaabcxyzpqrrrabbxyyyypqqqqqAzz" nil "aaabcxyzpqrrrabbxyyyypqqqqqAzz" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (23 "\"aaabcxyzpqrrrabbxyyyypqqqqqqAzz\" =~ /a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz/" "a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz" nil nil nil nil "aaabcxyzpqrrrabbxyyyypqqqqqqAzz" nil "aaabcxyzpqrrrabbxyyyypqqqqqqAzz" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (24 "\"aaaabcxyzpqrrrabbxyyyypqAzz\" =~ /a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz/" "a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz" nil nil nil nil "aaaabcxyzpqrrrabbxyyyypqAzz" nil "aaaabcxyzpqrrrabbxyyyypqAzz" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (25 "\"abxyzzpqrrrabbxyyyypqAzz\" =~ /a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz/" "a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz" nil nil nil nil "abxyzzpqrrrabbxyyyypqAzz" nil "abxyzzpqrrrabbxyyyypqAzz" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (26 "\"aabxyzzzpqrrrabbxyyyypqAzz\" =~ /a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz/" "a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz" nil nil nil nil "aabxyzzzpqrrrabbxyyyypqAzz" nil "aabxyzzzpqrrrabbxyyyypqAzz" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (27 "\"aaabxyzzzzpqrrrabbxyyyypqAzz\" =~ /a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz/" "a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz" nil nil nil nil "aaabxyzzzzpqrrrabbxyyyypqAzz" nil "aaabxyzzzzpqrrrabbxyyyypqAzz" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (28 "\"aaaabxyzzzzpqrrrabbxyyyypqAzz\" =~ /a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz/" "a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz" nil nil nil nil "aaaabxyzzzzpqrrrabbxyyyypqAzz" nil "aaaabxyzzzzpqrrrabbxyyyypqAzz" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (29 "\"abcxyzzpqrrrabbxyyyypqAzz\" =~ /a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz/" "a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz" nil nil nil nil "abcxyzzpqrrrabbxyyyypqAzz" nil "abcxyzzpqrrrabbxyyyypqAzz" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (30 "\"aabcxyzzzpqrrrabbxyyyypqAzz\" =~ /a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz/" "a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz" nil nil nil nil "aabcxyzzzpqrrrabbxyyyypqAzz" nil "aabcxyzzzpqrrrabbxyyyypqAzz" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (31 "\"aaabcxyzzzzpqrrrabbxyyyypqAzz\" =~ /a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz/" "a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz" nil nil nil nil "aaabcxyzzzzpqrrrabbxyyyypqAzz" nil "aaabcxyzzzzpqrrrabbxyyyypqAzz" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (32 "\"aaaabcxyzzzzpqrrrabbxyyyypqAzz\" =~ /a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz/" "a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz" nil nil nil nil "aaaabcxyzzzzpqrrrabbxyyyypqAzz" nil "aaaabcxyzzzzpqrrrabbxyyyypqAzz" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (33 "\"aaaabcxyzzzzpqrrrabbbxyyyypqAzz\" =~ /a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz/" "a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz" nil nil nil nil "aaaabcxyzzzzpqrrrabbbxyyyypqAzz" nil "aaaabcxyzzzzpqrrrabbbxyyyypqAzz" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (34 "\"aaaabcxyzzzzpqrrrabbbxyyyyypqAzz\" =~ /a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz/" "a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz" nil nil nil nil "aaaabcxyzzzzpqrrrabbbxyyyyypqAzz" nil "aaaabcxyzzzzpqrrrabbbxyyyyypqAzz" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (35 "\"aaabcxyzpqrrrabbxyyyypABzz\" =~ /a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz/" "a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz" nil nil nil nil "aaabcxyzpqrrrabbxyyyypABzz" nil "aaabcxyzpqrrrabbxyyyypABzz" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (36 "\"aaabcxyzpqrrrabbxyyyypABBzz\" =~ /a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz/" "a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz" nil nil nil nil "aaabcxyzpqrrrabbxyyyypABBzz" nil "aaabcxyzpqrrrabbxyyyypABBzz" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (37 "\">>>aaabxyzpqrrrabbxyyyypqAzz\" =~ /a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz/" "a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz" nil nil nil nil ">>>aaabxyzpqrrrabbxyyyypqAzz" nil "aaabxyzpqrrrabbxyyyypqAzz" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (38 "\">aaaabxyzpqrrrabbxyyyypqAzz\" =~ /a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz/" "a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz" nil nil nil nil ">aaaabxyzpqrrrabbxyyyypqAzz" nil "aaaabxyzpqrrrabbxyyyypqAzz" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (39 "\">>>>abcxyzpqrrrabbxyyyypqAzz\" =~ /a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz/" "a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz" nil nil nil nil ">>>>abcxyzpqrrrabbxyyyypqAzz" nil "abcxyzpqrrrabbxyyyypqAzz" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (40 "\"abxyzpqrrabbxyyyypqAzz\" =~ /a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz/" "a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz" nil nil nil nil "abxyzpqrrabbxyyyypqAzz" nil nil nil) (41 "\"abxyzpqrrrrabbxyyyypqAzz\" =~ /a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz/" "a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz" nil nil nil nil "abxyzpqrrrrabbxyyyypqAzz" nil nil nil) (42 "\"abxyzpqrrrabxyyyypqAzz\" =~ /a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz/" "a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz" nil nil nil nil "abxyzpqrrrabxyyyypqAzz" nil nil nil) (43 "\"aaaabcxyzzzzpqrrrabbbxyyyyyypqAzz\" =~ /a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz/" "a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz" nil nil nil nil "aaaabcxyzzzzpqrrrabbbxyyyyyypqAzz" nil nil nil) (44 "\"aaaabcxyzzzzpqrrrabbbxyyypqAzz\" =~ /a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz/" "a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz" nil nil nil nil "aaaabcxyzzzzpqrrrabbbxyyypqAzz" nil nil nil) (45 "\"aaabcxyzpqrrrabbxyyyypqqqqqqqAzz\" =~ /a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz/" "a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz" nil nil nil nil "aaabcxyzpqrrrabbxyyyypqqqqqqqAzz" nil nil nil) (46 "\"abczz\" =~ /^(abc){1,2}zz/" "^(abc){1,2}zz" nil nil nil nil "abczz" nil "abczz" ("abc" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (47 "\"abcabczz\" =~ /^(abc){1,2}zz/" "^(abc){1,2}zz" nil nil nil nil "abcabczz" nil "abcabczz" ("abc" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (48 "\"zz\" =~ /^(abc){1,2}zz/" "^(abc){1,2}zz" nil nil nil nil "zz" nil nil nil) (49 "\"abcabcabczz\" =~ /^(abc){1,2}zz/" "^(abc){1,2}zz" nil nil nil nil "abcabcabczz" nil nil nil) (50 "\">>abczz\" =~ /^(abc){1,2}zz/" "^(abc){1,2}zz" nil nil nil nil ">>abczz" nil nil nil) (51 "\"bc\" =~ /^(b+?|a){1,2}?c/" "^(b+?|a){1,2}?c" nil nil nil nil "bc" nil "bc" ("b" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (52 "\"bbc\" =~ /^(b+?|a){1,2}?c/" "^(b+?|a){1,2}?c" nil nil nil nil "bbc" nil "bbc" ("b" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (53 "\"bbbc\" =~ /^(b+?|a){1,2}?c/" "^(b+?|a){1,2}?c" nil nil nil nil "bbbc" nil "bbbc" ("bb" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (54 "\"bac\" =~ /^(b+?|a){1,2}?c/" "^(b+?|a){1,2}?c" nil nil nil nil "bac" nil "bac" ("a" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (55 "\"bbac\" =~ /^(b+?|a){1,2}?c/" "^(b+?|a){1,2}?c" nil nil nil nil "bbac" nil "bbac" ("a" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (56 "\"aac\" =~ /^(b+?|a){1,2}?c/" "^(b+?|a){1,2}?c" nil nil nil nil "aac" nil "aac" ("a" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (57 "\"abbbbbbbbbbbc\" =~ /^(b+?|a){1,2}?c/" "^(b+?|a){1,2}?c" nil nil nil nil "abbbbbbbbbbbc" nil "abbbbbbbbbbbc" ("bbbbbbbbbbb" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (58 "\"bbbbbbbbbbbac\" =~ /^(b+?|a){1,2}?c/" "^(b+?|a){1,2}?c" nil nil nil nil "bbbbbbbbbbbac" nil "bbbbbbbbbbbac" ("a" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (59 "\"aaac\" =~ /^(b+?|a){1,2}?c/" "^(b+?|a){1,2}?c" nil nil nil nil "aaac" nil nil nil) (60 "\"abbbbbbbbbbbac\" =~ /^(b+?|a){1,2}?c/" "^(b+?|a){1,2}?c" nil nil nil nil "abbbbbbbbbbbac" nil nil nil) (61 "\"bc\" =~ /^(b+|a){1,2}c/" "^(b+|a){1,2}c" nil nil nil nil "bc" nil "bc" ("b" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (62 "\"bbc\" =~ /^(b+|a){1,2}c/" "^(b+|a){1,2}c" nil nil nil nil "bbc" nil "bbc" ("bb" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (63 "\"bbbc\" =~ /^(b+|a){1,2}c/" "^(b+|a){1,2}c" nil nil nil nil "bbbc" nil "bbbc" ("bbb" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (64 "\"bac\" =~ /^(b+|a){1,2}c/" "^(b+|a){1,2}c" nil nil nil nil "bac" nil "bac" ("a" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (65 "\"bbac\" =~ /^(b+|a){1,2}c/" "^(b+|a){1,2}c" nil nil nil nil "bbac" nil "bbac" ("a" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (66 "\"aac\" =~ /^(b+|a){1,2}c/" "^(b+|a){1,2}c" nil nil nil nil "aac" nil "aac" ("a" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (67 "\"abbbbbbbbbbbc\" =~ /^(b+|a){1,2}c/" "^(b+|a){1,2}c" nil nil nil nil "abbbbbbbbbbbc" nil "abbbbbbbbbbbc" ("bbbbbbbbbbb" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (68 "\"bbbbbbbbbbbac\" =~ /^(b+|a){1,2}c/" "^(b+|a){1,2}c" nil nil nil nil "bbbbbbbbbbbac" nil "bbbbbbbbbbbac" ("a" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (69 "\"aaac\" =~ /^(b+|a){1,2}c/" "^(b+|a){1,2}c" nil nil nil nil "aaac" nil nil nil) (70 "\"abbbbbbbbbbbac\" =~ /^(b+|a){1,2}c/" "^(b+|a){1,2}c" nil nil nil nil "abbbbbbbbbbbac" nil nil nil) (71 "\"bbc\" =~ /^(b+|a){1,2}?bc/" "^(b+|a){1,2}?bc" nil nil nil nil "bbc" nil "bbc" ("b" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (72 "\"babc\" =~ /^(b*|ba){1,2}?bc/" "^(b*|ba){1,2}?bc" nil nil nil nil "babc" nil "babc" ("ba" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (73 "\"bbabc\" =~ /^(b*|ba){1,2}?bc/" "^(b*|ba){1,2}?bc" nil nil nil nil "bbabc" nil "bbabc" ("ba" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (74 "\"bababc\" =~ /^(b*|ba){1,2}?bc/" "^(b*|ba){1,2}?bc" nil nil nil nil "bababc" nil "bababc" ("ba" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (75 "\"bababbc\" =~ /^(b*|ba){1,2}?bc/" "^(b*|ba){1,2}?bc" nil nil nil nil "bababbc" nil nil nil) (76 "\"babababc\" =~ /^(b*|ba){1,2}?bc/" "^(b*|ba){1,2}?bc" nil nil nil nil "babababc" nil nil nil) (77 "\"babc\" =~ /^(ba|b*){1,2}?bc/" "^(ba|b*){1,2}?bc" nil nil nil nil "babc" nil "babc" ("ba" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (78 "\"bbabc\" =~ /^(ba|b*){1,2}?bc/" "^(ba|b*){1,2}?bc" nil nil nil nil "bbabc" nil "bbabc" ("ba" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (79 "\"bababc\" =~ /^(ba|b*){1,2}?bc/" "^(ba|b*){1,2}?bc" nil nil nil nil "bababc" nil "bababc" ("ba" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (80 "\"bababbc\" =~ /^(ba|b*){1,2}?bc/" "^(ba|b*){1,2}?bc" nil nil nil nil "bababbc" nil nil nil) (81 "\"babababc\" =~ /^(ba|b*){1,2}?bc/" "^(ba|b*){1,2}?bc" nil nil nil nil "babababc" nil nil nil) (82 "\"\\x01\\x01\\e;z\" =~ /^\\ca\\cA\\c[\\c{\\c:/" "^\\ca\\cA\\c[\\c{\\c:" nil nil nil nil ("" 1 1 27 ";z") nil ("" 1 1 27 ";z") (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (83 "\"athing\" =~ /^[ab\\]cde]/" "^[ab\\]cde]" nil nil nil nil "athing" nil "a" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (84 "\"bthing\" =~ /^[ab\\]cde]/" "^[ab\\]cde]" nil nil nil nil "bthing" nil "b" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (85 "\"]thing\" =~ /^[ab\\]cde]/" "^[ab\\]cde]" nil nil nil nil "]thing" nil "]" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (86 "\"cthing\" =~ /^[ab\\]cde]/" "^[ab\\]cde]" nil nil nil nil "cthing" nil "c" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (87 "\"dthing\" =~ /^[ab\\]cde]/" "^[ab\\]cde]" nil nil nil nil "dthing" nil "d" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (88 "\"ething\" =~ /^[ab\\]cde]/" "^[ab\\]cde]" nil nil nil nil "ething" nil "e" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (89 "\"fthing\" =~ /^[ab\\]cde]/" "^[ab\\]cde]" nil nil nil nil "fthing" nil nil nil) (90 "\"[thing\" =~ /^[ab\\]cde]/" "^[ab\\]cde]" nil nil nil nil "[thing" nil nil nil) (91 "\"\\\\thing\" =~ /^[ab\\]cde]/" "^[ab\\]cde]" nil nil nil nil "\\thing" nil nil nil) (92 "\"]thing\" =~ /^[]cde]/" "^[]cde]" nil nil nil nil "]thing" nil "]" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (93 "\"cthing\" =~ /^[]cde]/" "^[]cde]" nil nil nil nil "cthing" nil "c" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (94 "\"dthing\" =~ /^[]cde]/" "^[]cde]" nil nil nil nil "dthing" nil "d" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (95 "\"ething\" =~ /^[]cde]/" "^[]cde]" nil nil nil nil "ething" nil "e" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (96 "\"athing\" =~ /^[]cde]/" "^[]cde]" nil nil nil nil "athing" nil nil nil) (97 "\"fthing\" =~ /^[]cde]/" "^[]cde]" nil nil nil nil "fthing" nil nil nil) (98 "\"fthing\" =~ /^[^ab\\]cde]/" "^[^ab\\]cde]" nil nil nil nil "fthing" nil "f" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (99 "\"[thing\" =~ /^[^ab\\]cde]/" "^[^ab\\]cde]" nil nil nil nil "[thing" nil "[" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (100 "\"\\\\thing\" =~ /^[^ab\\]cde]/" "^[^ab\\]cde]" nil nil nil nil "\\thing" nil "\\" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (101 "\"athing\" =~ /^[^ab\\]cde]/" "^[^ab\\]cde]" nil nil nil nil "athing" nil nil nil) (102 "\"bthing\" =~ /^[^ab\\]cde]/" "^[^ab\\]cde]" nil nil nil nil "bthing" nil nil nil) (103 "\"]thing\" =~ /^[^ab\\]cde]/" "^[^ab\\]cde]" nil nil nil nil "]thing" nil nil nil) (104 "\"cthing\" =~ /^[^ab\\]cde]/" "^[^ab\\]cde]" nil nil nil nil "cthing" nil nil nil) (105 "\"dthing\" =~ /^[^ab\\]cde]/" "^[^ab\\]cde]" nil nil nil nil "dthing" nil nil nil) (106 "\"ething\" =~ /^[^ab\\]cde]/" "^[^ab\\]cde]" nil nil nil nil "ething" nil nil nil) (107 "\"athing\" =~ /^[^]cde]/" "^[^]cde]" nil nil nil nil "athing" nil "a" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (108 "\"fthing\" =~ /^[^]cde]/" "^[^]cde]" nil nil nil nil "fthing" nil "f" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (109 "\"]thing\" =~ /^[^]cde]/" "^[^]cde]" nil nil nil nil "]thing" nil nil nil) (110 "\"cthing\" =~ /^[^]cde]/" "^[^]cde]" nil nil nil nil "cthing" nil nil nil) (111 "\"dthing\" =~ /^[^]cde]/" "^[^]cde]" nil nil nil nil "dthing" nil nil nil) (112 "\"ething\" =~ /^[^]cde]/" "^[^]cde]" nil nil nil nil "ething" nil nil nil) (113 ("\"" 129 "\" =~ /^\\" 129 "/") "^\\" nil nil nil nil ("" 129) nil ("" 129) (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (114 ("\"" 255 "\" =~ /^" 255 "/") "^ÿ" nil nil nil nil ("" 255) nil ("" 255) (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (115 "\"0\" =~ /^[0-9]+$/" "^[0-9]+$" nil nil nil nil "0" nil "0" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (116 "\"1\" =~ /^[0-9]+$/" "^[0-9]+$" nil nil nil nil "1" nil "1" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (117 "\"2\" =~ /^[0-9]+$/" "^[0-9]+$" nil nil nil nil "2" nil "2" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (118 "\"3\" =~ /^[0-9]+$/" "^[0-9]+$" nil nil nil nil "3" nil "3" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (119 "\"4\" =~ /^[0-9]+$/" "^[0-9]+$" nil nil nil nil "4" nil "4" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (120 "\"5\" =~ /^[0-9]+$/" "^[0-9]+$" nil nil nil nil "5" nil "5" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (121 "\"6\" =~ /^[0-9]+$/" "^[0-9]+$" nil nil nil nil "6" nil "6" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (122 "\"7\" =~ /^[0-9]+$/" "^[0-9]+$" nil nil nil nil "7" nil "7" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (123 "\"8\" =~ /^[0-9]+$/" "^[0-9]+$" nil nil nil nil "8" nil "8" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (124 "\"9\" =~ /^[0-9]+$/" "^[0-9]+$" nil nil nil nil "9" nil "9" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (125 "\"10\" =~ /^[0-9]+$/" "^[0-9]+$" nil nil nil nil "10" nil "10" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (126 "\"100\" =~ /^[0-9]+$/" "^[0-9]+$" nil nil nil nil "100" nil "100" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (127 "\"abc\" =~ /^[0-9]+$/" "^[0-9]+$" nil nil nil nil "abc" nil nil nil) (128 "\"enter\" =~ /^.*nter/" "^.*nter" nil nil nil nil "enter" nil "enter" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (129 "\"inter\" =~ /^.*nter/" "^.*nter" nil nil nil nil "inter" nil "inter" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (130 "\"uponter\" =~ /^.*nter/" "^.*nter" nil nil nil nil "uponter" nil "uponter" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (131 "\"xxx0\" =~ /^xxx[0-9]+$/" "^xxx[0-9]+$" nil nil nil nil "xxx0" nil "xxx0" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (132 "\"xxx1234\" =~ /^xxx[0-9]+$/" "^xxx[0-9]+$" nil nil nil nil "xxx1234" nil "xxx1234" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (133 "\"xxx\" =~ /^xxx[0-9]+$/" "^xxx[0-9]+$" nil nil nil nil "xxx" nil nil nil) (134 "\"x123\" =~ /^.+[0-9][0-9][0-9]$/" "^.+[0-9][0-9][0-9]$" nil nil nil nil "x123" nil "x123" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (135 "\"xx123\" =~ /^.+[0-9][0-9][0-9]$/" "^.+[0-9][0-9][0-9]$" nil nil nil nil "xx123" nil "xx123" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (136 "\"123456\" =~ /^.+[0-9][0-9][0-9]$/" "^.+[0-9][0-9][0-9]$" nil nil nil nil "123456" nil "123456" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (137 "\"123\" =~ /^.+[0-9][0-9][0-9]$/" "^.+[0-9][0-9][0-9]$" nil nil nil nil "123" nil nil nil) (138 "\"x1234\" =~ /^.+[0-9][0-9][0-9]$/" "^.+[0-9][0-9][0-9]$" nil nil nil nil "x1234" nil "x1234" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (139 "\"x123\" =~ /^.+?[0-9][0-9][0-9]$/" "^.+?[0-9][0-9][0-9]$" nil nil nil nil "x123" nil "x123" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (140 "\"xx123\" =~ /^.+?[0-9][0-9][0-9]$/" "^.+?[0-9][0-9][0-9]$" nil nil nil nil "xx123" nil "xx123" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (141 "\"123456\" =~ /^.+?[0-9][0-9][0-9]$/" "^.+?[0-9][0-9][0-9]$" nil nil nil nil "123456" nil "123456" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (142 "\"123\" =~ /^.+?[0-9][0-9][0-9]$/" "^.+?[0-9][0-9][0-9]$" nil nil nil nil "123" nil nil nil) (143 "\"x1234\" =~ /^.+?[0-9][0-9][0-9]$/" "^.+?[0-9][0-9][0-9]$" nil nil nil nil "x1234" nil "x1234" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (144 "\"abc!pqr=apquxz.ixr.zzz.ac.uk\" =~ /^([^!]+)!(.+)=apquxz\\.ixr\\.zzz\\.ac\\.uk$/" "^([^!]+)!(.+)=apquxz\\.ixr\\.zzz\\.ac\\.uk$" nil nil nil nil "abc!pqr=apquxz.ixr.zzz.ac.uk" nil "abc!pqr=apquxz.ixr.zzz.ac.uk" ("abc" "pqr" nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (145 "\"!pqr=apquxz.ixr.zzz.ac.uk\" =~ /^([^!]+)!(.+)=apquxz\\.ixr\\.zzz\\.ac\\.uk$/" "^([^!]+)!(.+)=apquxz\\.ixr\\.zzz\\.ac\\.uk$" nil nil nil nil "!pqr=apquxz.ixr.zzz.ac.uk" nil nil nil) (146 "\"abc!=apquxz.ixr.zzz.ac.uk\" =~ /^([^!]+)!(.+)=apquxz\\.ixr\\.zzz\\.ac\\.uk$/" "^([^!]+)!(.+)=apquxz\\.ixr\\.zzz\\.ac\\.uk$" nil nil nil nil "abc!=apquxz.ixr.zzz.ac.uk" nil nil nil) (147 "\"abc!pqr=apquxz:ixr.zzz.ac.uk\" =~ /^([^!]+)!(.+)=apquxz\\.ixr\\.zzz\\.ac\\.uk$/" "^([^!]+)!(.+)=apquxz\\.ixr\\.zzz\\.ac\\.uk$" nil nil nil nil "abc!pqr=apquxz:ixr.zzz.ac.uk" nil nil nil) (148 "\"abc!pqr=apquxz.ixr.zzz.ac.ukk\" =~ /^([^!]+)!(.+)=apquxz\\.ixr\\.zzz\\.ac\\.uk$/" "^([^!]+)!(.+)=apquxz\\.ixr\\.zzz\\.ac\\.uk$" nil nil nil nil "abc!pqr=apquxz.ixr.zzz.ac.ukk" nil nil nil) (149 "\"Well, we need a colon: somewhere\" =~ /:/" ":" nil nil nil nil "Well, we need a colon: somewhere" nil ":" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (150 "\"Fail if we don't\" =~ /:/" ":" nil nil nil nil "Fail if we don't" nil nil nil) (151 "\"0abc\" =~ /([\\da-f:]+)$/i" "([\\da-f:]+)$" t nil nil nil "0abc" nil "0abc" ("0abc" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (152 "\"abc\" =~ /([\\da-f:]+)$/i" "([\\da-f:]+)$" t nil nil nil "abc" nil "abc" ("abc" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (153 "\"fed\" =~ /([\\da-f:]+)$/i" "([\\da-f:]+)$" t nil nil nil "fed" nil "fed" ("fed" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (154 "\"E\" =~ /([\\da-f:]+)$/i" "([\\da-f:]+)$" t nil nil nil "E" nil "E" ("E" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (155 "\"::\" =~ /([\\da-f:]+)$/i" "([\\da-f:]+)$" t nil nil nil "::" nil "::" ("::" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (156 "\"5f03:12C0::932e\" =~ /([\\da-f:]+)$/i" "([\\da-f:]+)$" t nil nil nil "5f03:12C0::932e" nil "5f03:12C0::932e" ("5f03:12C0::932e" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (157 "\"fed def\" =~ /([\\da-f:]+)$/i" "([\\da-f:]+)$" t nil nil nil "fed def" nil "def" ("def" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (158 "\"Any old stuff\" =~ /([\\da-f:]+)$/i" "([\\da-f:]+)$" t nil nil nil "Any old stuff" nil "ff" ("ff" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (159 "\"0zzz\" =~ /([\\da-f:]+)$/i" "([\\da-f:]+)$" t nil nil nil "0zzz" nil nil nil) (160 "\"gzzz\" =~ /([\\da-f:]+)$/i" "([\\da-f:]+)$" t nil nil nil "gzzz" nil nil nil) (161 "\"fed\\x20\" =~ /([\\da-f:]+)$/i" "([\\da-f:]+)$" t nil nil nil "fed " nil nil nil) (162 "\"Any old rubbish\" =~ /([\\da-f:]+)$/i" "([\\da-f:]+)$" t nil nil nil "Any old rubbish" nil nil nil) (163 "\".1.2.3\" =~ /^.*\\.(\\d{1,3})\\.(\\d{1,3})\\.(\\d{1,3})$/" "^.*\\.(\\d{1,3})\\.(\\d{1,3})\\.(\\d{1,3})$" nil nil nil nil ".1.2.3" nil ".1.2.3" ("1" "2" "3" nil nil nil nil nil nil nil nil nil nil nil nil nil)) (164 "\"A.12.123.0\" =~ /^.*\\.(\\d{1,3})\\.(\\d{1,3})\\.(\\d{1,3})$/" "^.*\\.(\\d{1,3})\\.(\\d{1,3})\\.(\\d{1,3})$" nil nil nil nil "A.12.123.0" nil "A.12.123.0" ("12" "123" "0" nil nil nil nil nil nil nil nil nil nil nil nil nil)) (165 "\".1.2.3333\" =~ /^.*\\.(\\d{1,3})\\.(\\d{1,3})\\.(\\d{1,3})$/" "^.*\\.(\\d{1,3})\\.(\\d{1,3})\\.(\\d{1,3})$" nil nil nil nil ".1.2.3333" nil nil nil) (166 "\"1.2.3\" =~ /^.*\\.(\\d{1,3})\\.(\\d{1,3})\\.(\\d{1,3})$/" "^.*\\.(\\d{1,3})\\.(\\d{1,3})\\.(\\d{1,3})$" nil nil nil nil "1.2.3" nil nil nil) (167 "\"1234.2.3\" =~ /^.*\\.(\\d{1,3})\\.(\\d{1,3})\\.(\\d{1,3})$/" "^.*\\.(\\d{1,3})\\.(\\d{1,3})\\.(\\d{1,3})$" nil nil nil nil "1234.2.3" nil nil nil) (168 "\"1 IN SOA non-sp1 non-sp2(\" =~ /^(\\d+)\\s+IN\\s+SOA\\s+(\\S+)\\s+(\\S+)\\s*\\(\\s*$/" "^(\\d+)\\s+IN\\s+SOA\\s+(\\S+)\\s+(\\S+)\\s*\\(\\s*$" nil nil nil nil "1 IN SOA non-sp1 non-sp2(" nil "1 IN SOA non-sp1 non-sp2(" ("1" "non-sp1" "non-sp2" nil nil nil nil nil nil nil nil nil nil nil nil nil)) (169 "\"1 IN SOA non-sp1 non-sp2 (\" =~ /^(\\d+)\\s+IN\\s+SOA\\s+(\\S+)\\s+(\\S+)\\s*\\(\\s*$/" "^(\\d+)\\s+IN\\s+SOA\\s+(\\S+)\\s+(\\S+)\\s*\\(\\s*$" nil nil nil nil "1 IN SOA non-sp1 non-sp2 (" nil "1 IN SOA non-sp1 non-sp2 (" ("1" "non-sp1" "non-sp2" nil nil nil nil nil nil nil nil nil nil nil nil nil)) (170 "\"1IN SOA non-sp1 non-sp2(\" =~ /^(\\d+)\\s+IN\\s+SOA\\s+(\\S+)\\s+(\\S+)\\s*\\(\\s*$/" "^(\\d+)\\s+IN\\s+SOA\\s+(\\S+)\\s+(\\S+)\\s*\\(\\s*$" nil nil nil nil "1IN SOA non-sp1 non-sp2(" nil nil nil) (171 "\"a.\" =~ /^[a-zA-Z\\d][a-zA-Z\\d\\-]*(\\.[a-zA-Z\\d][a-zA-z\\d\\-]*)*\\.$/" "^[a-zA-Z\\d][a-zA-Z\\d\\-]*(\\.[a-zA-Z\\d][a-zA-z\\d\\-]*)*\\.$" nil nil nil nil "a." nil "a." (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (172 "\"Z.\" =~ /^[a-zA-Z\\d][a-zA-Z\\d\\-]*(\\.[a-zA-Z\\d][a-zA-z\\d\\-]*)*\\.$/" "^[a-zA-Z\\d][a-zA-Z\\d\\-]*(\\.[a-zA-Z\\d][a-zA-z\\d\\-]*)*\\.$" nil nil nil nil "Z." nil "Z." (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (173 "\"2.\" =~ /^[a-zA-Z\\d][a-zA-Z\\d\\-]*(\\.[a-zA-Z\\d][a-zA-z\\d\\-]*)*\\.$/" "^[a-zA-Z\\d][a-zA-Z\\d\\-]*(\\.[a-zA-Z\\d][a-zA-z\\d\\-]*)*\\.$" nil nil nil nil "2." nil "2." (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (174 "\"ab-c.pq-r.\" =~ /^[a-zA-Z\\d][a-zA-Z\\d\\-]*(\\.[a-zA-Z\\d][a-zA-z\\d\\-]*)*\\.$/" "^[a-zA-Z\\d][a-zA-Z\\d\\-]*(\\.[a-zA-Z\\d][a-zA-z\\d\\-]*)*\\.$" nil nil nil nil "ab-c.pq-r." nil "ab-c.pq-r." (".pq-r" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (175 "\"sxk.zzz.ac.uk.\" =~ /^[a-zA-Z\\d][a-zA-Z\\d\\-]*(\\.[a-zA-Z\\d][a-zA-z\\d\\-]*)*\\.$/" "^[a-zA-Z\\d][a-zA-Z\\d\\-]*(\\.[a-zA-Z\\d][a-zA-z\\d\\-]*)*\\.$" nil nil nil nil "sxk.zzz.ac.uk." nil "sxk.zzz.ac.uk." (".uk" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (176 "\"x-.y-.\" =~ /^[a-zA-Z\\d][a-zA-Z\\d\\-]*(\\.[a-zA-Z\\d][a-zA-z\\d\\-]*)*\\.$/" "^[a-zA-Z\\d][a-zA-Z\\d\\-]*(\\.[a-zA-Z\\d][a-zA-z\\d\\-]*)*\\.$" nil nil nil nil "x-.y-." nil "x-.y-." (".y-" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (177 "\"-abc.peq.\" =~ /^[a-zA-Z\\d][a-zA-Z\\d\\-]*(\\.[a-zA-Z\\d][a-zA-z\\d\\-]*)*\\.$/" "^[a-zA-Z\\d][a-zA-Z\\d\\-]*(\\.[a-zA-Z\\d][a-zA-z\\d\\-]*)*\\.$" nil nil nil nil "-abc.peq." nil nil nil) (178 "\"*.a\" =~ /^\\*\\.[a-z]([a-z\\-\\d]*[a-z\\d]+)?(\\.[a-z]([a-z\\-\\d]*[a-z\\d]+)?)*$/" "^\\*\\.[a-z]([a-z\\-\\d]*[a-z\\d]+)?(\\.[a-z]([a-z\\-\\d]*[a-z\\d]+)?)*$" nil nil nil nil "*.a" nil "*.a" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (179 "\"*.b0-a\" =~ /^\\*\\.[a-z]([a-z\\-\\d]*[a-z\\d]+)?(\\.[a-z]([a-z\\-\\d]*[a-z\\d]+)?)*$/" "^\\*\\.[a-z]([a-z\\-\\d]*[a-z\\d]+)?(\\.[a-z]([a-z\\-\\d]*[a-z\\d]+)?)*$" nil nil nil nil "*.b0-a" nil "*.b0-a" ("0-a" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (180 "\"*.c3-b.c\" =~ /^\\*\\.[a-z]([a-z\\-\\d]*[a-z\\d]+)?(\\.[a-z]([a-z\\-\\d]*[a-z\\d]+)?)*$/" "^\\*\\.[a-z]([a-z\\-\\d]*[a-z\\d]+)?(\\.[a-z]([a-z\\-\\d]*[a-z\\d]+)?)*$" nil nil nil nil "*.c3-b.c" nil "*.c3-b.c" ("3-b" ".c" nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (181 "\"*.c-a.b-c\" =~ /^\\*\\.[a-z]([a-z\\-\\d]*[a-z\\d]+)?(\\.[a-z]([a-z\\-\\d]*[a-z\\d]+)?)*$/" "^\\*\\.[a-z]([a-z\\-\\d]*[a-z\\d]+)?(\\.[a-z]([a-z\\-\\d]*[a-z\\d]+)?)*$" nil nil nil nil "*.c-a.b-c" nil "*.c-a.b-c" ("-a" ".b-c" "-c" nil nil nil nil nil nil nil nil nil nil nil nil nil)) (182 "\"*.0\" =~ /^\\*\\.[a-z]([a-z\\-\\d]*[a-z\\d]+)?(\\.[a-z]([a-z\\-\\d]*[a-z\\d]+)?)*$/" "^\\*\\.[a-z]([a-z\\-\\d]*[a-z\\d]+)?(\\.[a-z]([a-z\\-\\d]*[a-z\\d]+)?)*$" nil nil nil nil "*.0" nil nil nil) (183 "\"*.a-\" =~ /^\\*\\.[a-z]([a-z\\-\\d]*[a-z\\d]+)?(\\.[a-z]([a-z\\-\\d]*[a-z\\d]+)?)*$/" "^\\*\\.[a-z]([a-z\\-\\d]*[a-z\\d]+)?(\\.[a-z]([a-z\\-\\d]*[a-z\\d]+)?)*$" nil nil nil nil "*.a-" nil nil nil) (184 "\"*.a-b.c-\" =~ /^\\*\\.[a-z]([a-z\\-\\d]*[a-z\\d]+)?(\\.[a-z]([a-z\\-\\d]*[a-z\\d]+)?)*$/" "^\\*\\.[a-z]([a-z\\-\\d]*[a-z\\d]+)?(\\.[a-z]([a-z\\-\\d]*[a-z\\d]+)?)*$" nil nil nil nil "*.a-b.c-" nil nil nil) (185 "\"*.c-a.0-c\" =~ /^\\*\\.[a-z]([a-z\\-\\d]*[a-z\\d]+)?(\\.[a-z]([a-z\\-\\d]*[a-z\\d]+)?)*$/" "^\\*\\.[a-z]([a-z\\-\\d]*[a-z\\d]+)?(\\.[a-z]([a-z\\-\\d]*[a-z\\d]+)?)*$" nil nil nil nil "*.c-a.0-c" nil nil nil) (186 "\"abde\" =~ /^(?=ab(de))(abd)(e)/" "^(?=ab(de))(abd)(e)" nil nil nil nil "abde" nil "abde" ("de" "abd" "e" nil nil nil nil nil nil nil nil nil nil nil nil nil)) (187 "\"abdf\" =~ /^(?!(ab)de|x)(abd)(f)/" "^(?!(ab)de|x)(abd)(f)" nil nil nil nil "abdf" nil "abdf" (nil "abd" "f" nil nil nil nil nil nil nil nil nil nil nil nil nil)) (188 "\"abcd\" =~ /^(?=(ab(cd)))(ab)/" "^(?=(ab(cd)))(ab)" nil nil nil nil "abcd" nil "ab" ("abcd" "cd" "ab" nil nil nil nil nil nil nil nil nil nil nil nil nil)) (189 "\"a.b.c.d\" =~ /^[\\da-f](\\.[\\da-f])*$/i" "^[\\da-f](\\.[\\da-f])*$" t nil nil nil "a.b.c.d" nil "a.b.c.d" (".d" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (190 "\"A.B.C.D\" =~ /^[\\da-f](\\.[\\da-f])*$/i" "^[\\da-f](\\.[\\da-f])*$" t nil nil nil "A.B.C.D" nil "A.B.C.D" (".D" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (191 "\"a.b.c.1.2.3.C\" =~ /^[\\da-f](\\.[\\da-f])*$/i" "^[\\da-f](\\.[\\da-f])*$" t nil nil nil "a.b.c.1.2.3.C" nil "a.b.c.1.2.3.C" (".C" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (192 "\"\\\"1234\\\"\" =~ /^\\\".*\\\"\\s*(;.*)?$/" "^\\\".*\\\"\\s*(;.*)?$" nil nil nil nil "\"1234\"" nil "\"1234\"" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (193 "\"\\\"abcd\\\" ;\" =~ /^\\\".*\\\"\\s*(;.*)?$/" "^\\\".*\\\"\\s*(;.*)?$" nil nil nil nil "\"abcd\" ;" nil "\"abcd\" ;" (";" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (194 "\"\\\"\\\" ; rhubarb\" =~ /^\\\".*\\\"\\s*(;.*)?$/" "^\\\".*\\\"\\s*(;.*)?$" nil nil nil nil "\"\" ; rhubarb" nil "\"\" ; rhubarb" ("; rhubarb" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (195 "\"\\\"1234\\\" : things\" =~ /^\\\".*\\\"\\s*(;.*)?$/" "^\\\".*\\\"\\s*(;.*)?$" nil nil nil nil "\"1234\" : things" nil nil nil) (196 "\"\\\" =~ /^$/" "^$" nil nil nil nil "" nil "" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (197 "\"ab c\" =~ / ^ a (?# begins with a) b\\sc (?# then b c) $ (?# then end)/x" " ^ a (?# begins with a) b\\sc (?# then b c) $ (?# then end)" nil nil nil t "ab c" nil "ab c" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (198 "\"abc\" =~ / ^ a (?# begins with a) b\\sc (?# then b c) $ (?# then end)/x" " ^ a (?# begins with a) b\\sc (?# then b c) $ (?# then end)" nil nil nil t "abc" nil nil nil) (199 "\"ab cde\" =~ / ^ a (?# begins with a) b\\sc (?# then b c) $ (?# then end)/x" " ^ a (?# begins with a) b\\sc (?# then b c) $ (?# then end)" nil nil nil t "ab cde" nil nil nil) (200 "\"ab c\" =~ /(?x) ^ a (?# begins with a) b\\sc (?# then b c) $ (?# then end)/" "(?x) ^ a (?# begins with a) b\\sc (?# then b c) $ (?# then end)" nil nil nil nil "ab c" nil "ab c" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (201 "\"abc\" =~ /(?x) ^ a (?# begins with a) b\\sc (?# then b c) $ (?# then end)/" "(?x) ^ a (?# begins with a) b\\sc (?# then b c) $ (?# then end)" nil nil nil nil "abc" nil nil nil) (202 "\"ab cde\" =~ /(?x) ^ a (?# begins with a) b\\sc (?# then b c) $ (?# then end)/" "(?x) ^ a (?# begins with a) b\\sc (?# then b c) $ (?# then end)" nil nil nil nil "ab cde" nil nil nil) (203 "\"a bcd\" =~ /^ a\\ b[c ]d $/x" "^ a\\ b[c ]d $" nil nil nil t "a bcd" nil "a bcd" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (204 "\"a b d\" =~ /^ a\\ b[c ]d $/x" "^ a\\ b[c ]d $" nil nil nil t "a b d" nil "a b d" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (205 "\"abcd\" =~ /^ a\\ b[c ]d $/x" "^ a\\ b[c ]d $" nil nil nil t "abcd" nil nil nil) (206 "\"ab d\" =~ /^ a\\ b[c ]d $/x" "^ a\\ b[c ]d $" nil nil nil t "ab d" nil nil nil) (207 "\"abcdefhijklm\" =~ /^(a(b(c)))(d(e(f)))(h(i(j)))(k(l(m)))$/" "^(a(b(c)))(d(e(f)))(h(i(j)))(k(l(m)))$" nil nil nil nil "abcdefhijklm" nil "abcdefhijklm" ("abc" "bc" "c" "def" "ef" "f" "hij" "ij" "j" "klm" "lm" "m" nil nil nil nil)) (208 "\"abcdefhijklm\" =~ /^(?:a(b(c)))(?:d(e(f)))(?:h(i(j)))(?:k(l(m)))$/" "^(?:a(b(c)))(?:d(e(f)))(?:h(i(j)))(?:k(l(m)))$" nil nil nil nil "abcdefhijklm" nil "abcdefhijklm" ("bc" "c" "ef" "f" "ij" "j" "lm" "m" nil nil nil nil nil nil nil nil)) (209 "\"a+ Z0+\\x08\\n\\x1d\\x12\" =~ /^[\\w][\\W][\\s][\\S][\\d][\\D][\\b][\\n][\\c]][\\022]/" "^[\\w][\\W][\\s][\\S][\\d][\\D][\\b][\\n][\\c]][\\022]" nil nil nil nil ("a+ Z0+" 8 10 29 18) nil ("a+ Z0+" 8 10 29 18) (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (210 "\".^\\$(*+)|{?,?}\" =~ /^[.^$|()*+?{,}]+/" "^[.^$|()*+?{,}]+" nil nil nil nil ".^$(*+)|{?,?}" nil ".^$(*+)|{?,?}" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (211 "\"z\" =~ /^a*\\w/" "^a*\\w" nil nil nil nil "z" nil "z" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (212 "\"az\" =~ /^a*\\w/" "^a*\\w" nil nil nil nil "az" nil "az" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (213 "\"aaaz\" =~ /^a*\\w/" "^a*\\w" nil nil nil nil "aaaz" nil "aaaz" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (214 "\"a\" =~ /^a*\\w/" "^a*\\w" nil nil nil nil "a" nil "a" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (215 "\"aa\" =~ /^a*\\w/" "^a*\\w" nil nil nil nil "aa" nil "aa" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (216 "\"aaaa\" =~ /^a*\\w/" "^a*\\w" nil nil nil nil "aaaa" nil "aaaa" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (217 "\"a+\" =~ /^a*\\w/" "^a*\\w" nil nil nil nil "a+" nil "a" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (218 "\"aa+\" =~ /^a*\\w/" "^a*\\w" nil nil nil nil "aa+" nil "aa" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (219 "\"z\" =~ /^a*?\\w/" "^a*?\\w" nil nil nil nil "z" nil "z" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (220 "\"az\" =~ /^a*?\\w/" "^a*?\\w" nil nil nil nil "az" nil "a" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (221 "\"aaaz\" =~ /^a*?\\w/" "^a*?\\w" nil nil nil nil "aaaz" nil "a" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (222 "\"a\" =~ /^a*?\\w/" "^a*?\\w" nil nil nil nil "a" nil "a" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (223 "\"aa\" =~ /^a*?\\w/" "^a*?\\w" nil nil nil nil "aa" nil "a" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (224 "\"aaaa\" =~ /^a*?\\w/" "^a*?\\w" nil nil nil nil "aaaa" nil "a" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (225 "\"a+\" =~ /^a*?\\w/" "^a*?\\w" nil nil nil nil "a+" nil "a" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (226 "\"aa+\" =~ /^a*?\\w/" "^a*?\\w" nil nil nil nil "aa+" nil "a" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (227 "\"az\" =~ /^a+\\w/" "^a+\\w" nil nil nil nil "az" nil "az" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (228 "\"aaaz\" =~ /^a+\\w/" "^a+\\w" nil nil nil nil "aaaz" nil "aaaz" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (229 "\"aa\" =~ /^a+\\w/" "^a+\\w" nil nil nil nil "aa" nil "aa" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (230 "\"aaaa\" =~ /^a+\\w/" "^a+\\w" nil nil nil nil "aaaa" nil "aaaa" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (231 "\"aa+\" =~ /^a+\\w/" "^a+\\w" nil nil nil nil "aa+" nil "aa" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (232 "\"az\" =~ /^a+?\\w/" "^a+?\\w" nil nil nil nil "az" nil "az" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (233 "\"aaaz\" =~ /^a+?\\w/" "^a+?\\w" nil nil nil nil "aaaz" nil "aa" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (234 "\"aa\" =~ /^a+?\\w/" "^a+?\\w" nil nil nil nil "aa" nil "aa" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (235 "\"aaaa\" =~ /^a+?\\w/" "^a+?\\w" nil nil nil nil "aaaa" nil "aa" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (236 "\"aa+\" =~ /^a+?\\w/" "^a+?\\w" nil nil nil nil "aa+" nil "aa" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (237 "\"1234567890\" =~ /^\\d{8}\\w{2,}/" "^\\d{8}\\w{2,}" nil nil nil nil "1234567890" nil "1234567890" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (238 "\"12345678ab\" =~ /^\\d{8}\\w{2,}/" "^\\d{8}\\w{2,}" nil nil nil nil "12345678ab" nil "12345678ab" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (239 "\"12345678__\" =~ /^\\d{8}\\w{2,}/" "^\\d{8}\\w{2,}" nil nil nil nil "12345678__" nil "12345678__" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (240 "\"1234567\" =~ /^\\d{8}\\w{2,}/" "^\\d{8}\\w{2,}" nil nil nil nil "1234567" nil nil nil) (241 "\"uoie\" =~ /^[aeiou\\d]{4,5}$/" "^[aeiou\\d]{4,5}$" nil nil nil nil "uoie" nil "uoie" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (242 "\"1234\" =~ /^[aeiou\\d]{4,5}$/" "^[aeiou\\d]{4,5}$" nil nil nil nil "1234" nil "1234" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (243 "\"12345\" =~ /^[aeiou\\d]{4,5}$/" "^[aeiou\\d]{4,5}$" nil nil nil nil "12345" nil "12345" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (244 "\"aaaaa\" =~ /^[aeiou\\d]{4,5}$/" "^[aeiou\\d]{4,5}$" nil nil nil nil "aaaaa" nil "aaaaa" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (245 "\"123456\" =~ /^[aeiou\\d]{4,5}$/" "^[aeiou\\d]{4,5}$" nil nil nil nil "123456" nil nil nil) (246 "\"uoie\" =~ /^[aeiou\\d]{4,5}?/" "^[aeiou\\d]{4,5}?" nil nil nil nil "uoie" nil "uoie" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (247 "\"1234\" =~ /^[aeiou\\d]{4,5}?/" "^[aeiou\\d]{4,5}?" nil nil nil nil "1234" nil "1234" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (248 "\"12345\" =~ /^[aeiou\\d]{4,5}?/" "^[aeiou\\d]{4,5}?" nil nil nil nil "12345" nil "1234" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (249 "\"aaaaa\" =~ /^[aeiou\\d]{4,5}?/" "^[aeiou\\d]{4,5}?" nil nil nil nil "aaaaa" nil "aaaa" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (250 "\"123456\" =~ /^[aeiou\\d]{4,5}?/" "^[aeiou\\d]{4,5}?" nil nil nil nil "123456" nil "1234" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (251 "\"abc=abcabc\" =~ /\\A(abc|def)=(\\1){2,3}\\Z/" "\\A(abc|def)=(\\1){2,3}\\Z" nil nil nil nil "abc=abcabc" nil "abc=abcabc" ("abc" "abc" nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (252 "\"def=defdefdef\" =~ /\\A(abc|def)=(\\1){2,3}\\Z/" "\\A(abc|def)=(\\1){2,3}\\Z" nil nil nil nil "def=defdefdef" nil "def=defdefdef" ("def" "def" nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (253 "\"abc=defdef\" =~ /\\A(abc|def)=(\\1){2,3}\\Z/" "\\A(abc|def)=(\\1){2,3}\\Z" nil nil nil nil "abc=defdef" nil nil nil) (254 "\"abcdefghijkcda2\" =~ /^(a)(b)(c)(d)(e)(f)(g)(h)(i)(j)(k)\\11*(\\3\\4)\\1(?#)2$/" "^(a)(b)(c)(d)(e)(f)(g)(h)(i)(j)(k)\\11*(\\3\\4)\\1(?#)2$" nil nil nil nil "abcdefghijkcda2" nil "abcdefghijkcda2" ("a" "b" "c" "d" "e" "f" "g" "h" "i" "j" "k" "cd" nil nil nil nil)) (255 "\"abcdefghijkkkkcda2\" =~ /^(a)(b)(c)(d)(e)(f)(g)(h)(i)(j)(k)\\11*(\\3\\4)\\1(?#)2$/" "^(a)(b)(c)(d)(e)(f)(g)(h)(i)(j)(k)\\11*(\\3\\4)\\1(?#)2$" nil nil nil nil "abcdefghijkkkkcda2" nil "abcdefghijkkkkcda2" ("a" "b" "c" "d" "e" "f" "g" "h" "i" "j" "k" "cd" nil nil nil nil)) (256 "\"cataract cataract23\" =~ /(cat(a(ract|tonic)|erpillar)) \\1()2(3)/" "(cat(a(ract|tonic)|erpillar)) \\1()2(3)" nil nil nil nil "cataract cataract23" nil "cataract cataract23" ("cataract" "aract" "ract" "" "3" nil nil nil nil nil nil nil nil nil nil nil)) (257 "\"catatonic catatonic23\" =~ /(cat(a(ract|tonic)|erpillar)) \\1()2(3)/" "(cat(a(ract|tonic)|erpillar)) \\1()2(3)" nil nil nil nil "catatonic catatonic23" nil "catatonic catatonic23" ("catatonic" "atonic" "tonic" "" "3" nil nil nil nil nil nil nil nil nil nil nil)) (258 "\"caterpillar caterpillar23\" =~ /(cat(a(ract|tonic)|erpillar)) \\1()2(3)/" "(cat(a(ract|tonic)|erpillar)) \\1()2(3)" nil nil nil nil "caterpillar caterpillar23" nil "caterpillar caterpillar23" ("caterpillar" "erpillar" nil "" "3" nil nil nil nil nil nil nil nil nil nil nil)) (259 "\"From abcd Mon Sep 01 12:33:02 1997\" =~ /^From +([^ ]+) +[a-zA-Z][a-zA-Z][a-zA-Z] +[a-zA-Z][a-zA-Z][a-zA-Z] +[0-9]?[0-9] +[0-9][0-9]:[0-9][0-9]/" "^From +([^ ]+) +[a-zA-Z][a-zA-Z][a-zA-Z] +[a-zA-Z][a-zA-Z][a-zA-Z] +[0-9]?[0-9] +[0-9][0-9]:[0-9][0-9]" nil nil nil nil "From abcd Mon Sep 01 12:33:02 1997" nil "From abcd Mon Sep 01 12:33" ("abcd" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (260 "\"From abcd Mon Sep 01 12:33:02 1997\" =~ /^From\\s+\\S+\\s+([a-zA-Z]{3}\\s+){2}\\d{1,2}\\s+\\d\\d:\\d\\d/" "^From\\s+\\S+\\s+([a-zA-Z]{3}\\s+){2}\\d{1,2}\\s+\\d\\d:\\d\\d" nil nil nil nil "From abcd Mon Sep 01 12:33:02 1997" nil "From abcd Mon Sep 01 12:33" ("Sep " nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (261 "\"From abcd Mon Sep 1 12:33:02 1997\" =~ /^From\\s+\\S+\\s+([a-zA-Z]{3}\\s+){2}\\d{1,2}\\s+\\d\\d:\\d\\d/" "^From\\s+\\S+\\s+([a-zA-Z]{3}\\s+){2}\\d{1,2}\\s+\\d\\d:\\d\\d" nil nil nil nil "From abcd Mon Sep 1 12:33:02 1997" nil "From abcd Mon Sep 1 12:33" ("Sep " nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (262 "\"From abcd Sep 01 12:33:02 1997\" =~ /^From\\s+\\S+\\s+([a-zA-Z]{3}\\s+){2}\\d{1,2}\\s+\\d\\d:\\d\\d/" "^From\\s+\\S+\\s+([a-zA-Z]{3}\\s+){2}\\d{1,2}\\s+\\d\\d:\\d\\d" nil nil nil nil "From abcd Sep 01 12:33:02 1997" nil nil nil) (263 "\"12\\n34\" =~ /^12.34/s" "^12.34" nil nil t nil "12 34" nil "12 34" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (264 "\"12\\r34\" =~ /^12.34/s" "^12.34" nil nil t nil ("12" 13 "34") nil ("12" 13 "34") (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (265 "\"the quick brown\\t fox\" =~ /\\w+(?=\\t)/" "\\w+(?=\\t)" nil nil nil nil ("the quick brown" 9 " fox") nil "brown" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (266 "\"foobar is foolish see?\" =~ /foo(?!bar)(.*)/" "foo(?!bar)(.*)" nil nil nil nil "foobar is foolish see?" nil "foolish see?" ("lish see?" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (267 "\"foobar crowbar etc\" =~ /(?:(?!foo)...|^.{0,2})bar(.*)/" "(?:(?!foo)...|^.{0,2})bar(.*)" nil nil nil nil "foobar crowbar etc" nil "rowbar etc" (" etc" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (268 "\"barrel\" =~ /(?:(?!foo)...|^.{0,2})bar(.*)/" "(?:(?!foo)...|^.{0,2})bar(.*)" nil nil nil nil "barrel" nil "barrel" ("rel" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (269 "\"2barrel\" =~ /(?:(?!foo)...|^.{0,2})bar(.*)/" "(?:(?!foo)...|^.{0,2})bar(.*)" nil nil nil nil "2barrel" nil "2barrel" ("rel" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (270 "\"A barrel\" =~ /(?:(?!foo)...|^.{0,2})bar(.*)/" "(?:(?!foo)...|^.{0,2})bar(.*)" nil nil nil nil "A barrel" nil "A barrel" ("rel" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (271 "\"abc456\" =~ /^(\\D*)(?=\\d)(?!123)/" "^(\\D*)(?=\\d)(?!123)" nil nil nil nil "abc456" nil "abc" ("abc" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (272 "\"abc123\" =~ /^(\\D*)(?=\\d)(?!123)/" "^(\\D*)(?=\\d)(?!123)" nil nil nil nil "abc123" nil nil nil) (273 "\"1234\" =~ /^1234(?# test newlines inside)/" "^1234(?# test newlines inside)" nil nil nil nil "1234" nil "1234" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (274 "\"1234\" =~ /^1234 #comment in extended re /x" "^1234 #comment in extended re " nil nil nil t "1234" nil "1234" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (275 "\"abcd\" =~ /#rhubarb abcd/x" "#rhubarb abcd" nil nil nil t "abcd" nil "abcd" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (276 "\"abcd\" =~ /^abcd#rhubarb/x" "^abcd#rhubarb" nil nil nil t "abcd" nil "abcd" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (277 "\"aaab\" =~ /^(a)\\1{2,3}(.)/" "^(a)\\1{2,3}(.)" nil nil nil nil "aaab" nil "aaab" ("a" "b" nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (278 "\"aaaab\" =~ /^(a)\\1{2,3}(.)/" "^(a)\\1{2,3}(.)" nil nil nil nil "aaaab" nil "aaaab" ("a" "b" nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (279 "\"aaaaab\" =~ /^(a)\\1{2,3}(.)/" "^(a)\\1{2,3}(.)" nil nil nil nil "aaaaab" nil "aaaaa" ("a" "a" nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (280 "\"aaaaaab\" =~ /^(a)\\1{2,3}(.)/" "^(a)\\1{2,3}(.)" nil nil nil nil "aaaaaab" nil "aaaaa" ("a" "a" nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (281 "\"the abc\" =~ /(?!^)abc/" "(?!^)abc" nil nil nil nil "the abc" nil "abc" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (282 "\"abc\" =~ /(?!^)abc/" "(?!^)abc" nil nil nil nil "abc" nil nil nil) (283 "\"abc\" =~ /(?=^)abc/" "(?=^)abc" nil nil nil nil "abc" nil "abc" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (284 "\"the abc\" =~ /(?=^)abc/" "(?=^)abc" nil nil nil nil "the abc" nil nil nil) (285 "\"aabbbbb\" =~ /^[ab]{1,3}(ab*|b)/" "^[ab]{1,3}(ab*|b)" nil nil nil nil "aabbbbb" nil "aabb" ("b" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (286 "\"aabbbbb\" =~ /^[ab]{1,3}?(ab*|b)/" "^[ab]{1,3}?(ab*|b)" nil nil nil nil "aabbbbb" nil "aabbbbb" ("abbbbb" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (287 "\"aabbbbb\" =~ /^[ab]{1,3}?(ab*?|b)/" "^[ab]{1,3}?(ab*?|b)" nil nil nil nil "aabbbbb" nil "aa" ("a" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (288 "\"aabbbbb\" =~ /^[ab]{1,3}(ab*?|b)/" "^[ab]{1,3}(ab*?|b)" nil nil nil nil "aabbbbb" nil "aabb" ("b" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (289 "\"Alan Other \" =~ / (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* # optional leading comment (?: (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \" (?: # opening quote... [^\\\\\\x80-\\xff\\n\\015\"] # Anything except backslash and quote | # or \\\\ [^\\x80-\\xff] # Escaped something (something != CR) )* \" # closing quote ) # initial word (?: (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* \\. (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \" (?: # opening quote... [^\\\\\\x80-\\xff\\n\\015\"] # Anything except backslash and quote | # or \\\\ [^\\x80-\\xff] # Escaped something (something != CR) )* \" # closing quote ) )* # further okay, if led by a period (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* @ (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) # initial subdomain (?: # (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* \\. # if led by a period... (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) # ...further okay )* # address | # or (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \" (?: # opening quote... [^\\\\\\x80-\\xff\\n\\015\"] # Anything except backslash and quote | # or \\\\ [^\\x80-\\xff] # Escaped something (something != CR) )* \" # closing quote ) # one word, optionally followed by.... (?: [^()<>@,;:\".\\\\\\[\\]\\x80-\\xff\\000-\\010\\012-\\037] | # atom and space parts, or... \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) | # comments, or... \" (?: # opening quote... [^\\\\\\x80-\\xff\\n\\015\"] # Anything except backslash and quote | # or \\\\ [^\\x80-\\xff] # Escaped something (something != CR) )* \" # closing quote # quoted strings )* < (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* # leading < (?: @ (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) # initial subdomain (?: # (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* \\. # if led by a period... (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) # ...further okay )* (?: (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* , (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* @ (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) # initial subdomain (?: # (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* \\. # if led by a period... (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) # ...further okay )* )* # further okay, if led by comma : # closing colon (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* )? # optional route (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \" (?: # opening quote... [^\\\\\\x80-\\xff\\n\\015\"] # Anything except backslash and quote | # or \\\\ [^\\x80-\\xff] # Escaped something (something != CR) )* \" # closing quote ) # initial word (?: (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* \\. (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \" (?: # opening quote... [^\\\\\\x80-\\xff\\n\\015\"] # Anything except backslash and quote | # or \\\\ [^\\x80-\\xff] # Escaped something (something != CR) )* \" # closing quote ) )* # further okay, if led by a period (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* @ (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) # initial subdomain (?: # (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* \\. # if led by a period... (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) # ...further okay )* # address spec (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* > # trailing > # name and address ) (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* # optional trailing comment /x" " (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* # optional leading comment (?: (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \" (?: # opening quote... [^\\\\\\x80-\\xff\\n\\015\"] # Anything except backslash and quote | # or \\\\ [^\\x80-\\xff] # Escaped something (something != CR) )* \" # closing quote ) # initial word (?: (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* \\. (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \" (?: # opening quote... [^\\\\\\x80-\\xff\\n\\015\"] # Anything except backslash and quote | # or \\\\ [^\\x80-\\xff] # Escaped something (something != CR) )* \" # closing quote ) )* # further okay, if led by a period (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* @ (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) # initial subdomain (?: # (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* \\. # if led by a period... (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) # ...further okay )* # address | # or (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \" (?: # opening quote... [^\\\\\\x80-\\xff\\n\\015\"] # Anything except backslash and quote | # or \\\\ [^\\x80-\\xff] # Escaped something (something != CR) )* \" # closing quote ) # one word, optionally followed by.... (?: [^()<>@,;:\".\\\\\\[\\]\\x80-\\xff\\000-\\010\\012-\\037] | # atom and space parts, or... \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) | # comments, or... \" (?: # opening quote... [^\\\\\\x80-\\xff\\n\\015\"] # Anything except backslash and quote | # or \\\\ [^\\x80-\\xff] # Escaped something (something != CR) )* \" # closing quote # quoted strings )* < (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* # leading < (?: @ (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) # initial subdomain (?: # (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* \\. # if led by a period... (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) # ...further okay )* (?: (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* , (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* @ (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) # initial subdomain (?: # (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* \\. # if led by a period... (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) # ...further okay )* )* # further okay, if led by comma : # closing colon (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* )? # optional route (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \" (?: # opening quote... [^\\\\\\x80-\\xff\\n\\015\"] # Anything except backslash and quote | # or \\\\ [^\\x80-\\xff] # Escaped something (something != CR) )* \" # closing quote ) # initial word (?: (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* \\. (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \" (?: # opening quote... [^\\\\\\x80-\\xff\\n\\015\"] # Anything except backslash and quote | # or \\\\ [^\\x80-\\xff] # Escaped something (something != CR) )* \" # closing quote ) )* # further okay, if led by a period (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* @ (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) # initial subdomain (?: # (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* \\. # if led by a period... (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) # ...further okay )* # address spec (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* > # trailing > # name and address ) (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* # optional trailing comment " nil nil nil t "Alan Other " nil "Alan Other " (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (290 "\"\" =~ / (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* # optional leading comment (?: (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \" (?: # opening quote... [^\\\\\\x80-\\xff\\n\\015\"] # Anything except backslash and quote | # or \\\\ [^\\x80-\\xff] # Escaped something (something != CR) )* \" # closing quote ) # initial word (?: (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* \\. (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \" (?: # opening quote... [^\\\\\\x80-\\xff\\n\\015\"] # Anything except backslash and quote | # or \\\\ [^\\x80-\\xff] # Escaped something (something != CR) )* \" # closing quote ) )* # further okay, if led by a period (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* @ (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) # initial subdomain (?: # (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* \\. # if led by a period... (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) # ...further okay )* # address | # or (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \" (?: # opening quote... [^\\\\\\x80-\\xff\\n\\015\"] # Anything except backslash and quote | # or \\\\ [^\\x80-\\xff] # Escaped something (something != CR) )* \" # closing quote ) # one word, optionally followed by.... (?: [^()<>@,;:\".\\\\\\[\\]\\x80-\\xff\\000-\\010\\012-\\037] | # atom and space parts, or... \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) | # comments, or... \" (?: # opening quote... [^\\\\\\x80-\\xff\\n\\015\"] # Anything except backslash and quote | # or \\\\ [^\\x80-\\xff] # Escaped something (something != CR) )* \" # closing quote # quoted strings )* < (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* # leading < (?: @ (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) # initial subdomain (?: # (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* \\. # if led by a period... (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) # ...further okay )* (?: (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* , (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* @ (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) # initial subdomain (?: # (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* \\. # if led by a period... (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) # ...further okay )* )* # further okay, if led by comma : # closing colon (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* )? # optional route (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \" (?: # opening quote... [^\\\\\\x80-\\xff\\n\\015\"] # Anything except backslash and quote | # or \\\\ [^\\x80-\\xff] # Escaped something (something != CR) )* \" # closing quote ) # initial word (?: (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* \\. (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \" (?: # opening quote... [^\\\\\\x80-\\xff\\n\\015\"] # Anything except backslash and quote | # or \\\\ [^\\x80-\\xff] # Escaped something (something != CR) )* \" # closing quote ) )* # further okay, if led by a period (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* @ (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) # initial subdomain (?: # (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* \\. # if led by a period... (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) # ...further okay )* # address spec (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* > # trailing > # name and address ) (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* # optional trailing comment /x" " (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* # optional leading comment (?: (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \" (?: # opening quote... [^\\\\\\x80-\\xff\\n\\015\"] # Anything except backslash and quote | # or \\\\ [^\\x80-\\xff] # Escaped something (something != CR) )* \" # closing quote ) # initial word (?: (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* \\. (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \" (?: # opening quote... [^\\\\\\x80-\\xff\\n\\015\"] # Anything except backslash and quote | # or \\\\ [^\\x80-\\xff] # Escaped something (something != CR) )* \" # closing quote ) )* # further okay, if led by a period (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* @ (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) # initial subdomain (?: # (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* \\. # if led by a period... (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) # ...further okay )* # address | # or (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \" (?: # opening quote... [^\\\\\\x80-\\xff\\n\\015\"] # Anything except backslash and quote | # or \\\\ [^\\x80-\\xff] # Escaped something (something != CR) )* \" # closing quote ) # one word, optionally followed by.... (?: [^()<>@,;:\".\\\\\\[\\]\\x80-\\xff\\000-\\010\\012-\\037] | # atom and space parts, or... \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) | # comments, or... \" (?: # opening quote... [^\\\\\\x80-\\xff\\n\\015\"] # Anything except backslash and quote | # or \\\\ [^\\x80-\\xff] # Escaped something (something != CR) )* \" # closing quote # quoted strings )* < (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* # leading < (?: @ (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) # initial subdomain (?: # (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* \\. # if led by a period... (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) # ...further okay )* (?: (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* , (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* @ (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) # initial subdomain (?: # (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* \\. # if led by a period... (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) # ...further okay )* )* # further okay, if led by comma : # closing colon (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* )? # optional route (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \" (?: # opening quote... [^\\\\\\x80-\\xff\\n\\015\"] # Anything except backslash and quote | # or \\\\ [^\\x80-\\xff] # Escaped something (something != CR) )* \" # closing quote ) # initial word (?: (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* \\. (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \" (?: # opening quote... [^\\\\\\x80-\\xff\\n\\015\"] # Anything except backslash and quote | # or \\\\ [^\\x80-\\xff] # Escaped something (something != CR) )* \" # closing quote ) )* # further okay, if led by a period (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* @ (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) # initial subdomain (?: # (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* \\. # if led by a period... (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) # ...further okay )* # address spec (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* > # trailing > # name and address ) (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* # optional trailing comment " nil nil nil t "" nil "user@dom.ain" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (291 "\"user\\@dom.ain\" =~ / (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* # optional leading comment (?: (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \" (?: # opening quote... [^\\\\\\x80-\\xff\\n\\015\"] # Anything except backslash and quote | # or \\\\ [^\\x80-\\xff] # Escaped something (something != CR) )* \" # closing quote ) # initial word (?: (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* \\. (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \" (?: # opening quote... [^\\\\\\x80-\\xff\\n\\015\"] # Anything except backslash and quote | # or \\\\ [^\\x80-\\xff] # Escaped something (something != CR) )* \" # closing quote ) )* # further okay, if led by a period (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* @ (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) # initial subdomain (?: # (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* \\. # if led by a period... (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) # ...further okay )* # address | # or (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \" (?: # opening quote... [^\\\\\\x80-\\xff\\n\\015\"] # Anything except backslash and quote | # or \\\\ [^\\x80-\\xff] # Escaped something (something != CR) )* \" # closing quote ) # one word, optionally followed by.... (?: [^()<>@,;:\".\\\\\\[\\]\\x80-\\xff\\000-\\010\\012-\\037] | # atom and space parts, or... \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) | # comments, or... \" (?: # opening quote... [^\\\\\\x80-\\xff\\n\\015\"] # Anything except backslash and quote | # or \\\\ [^\\x80-\\xff] # Escaped something (something != CR) )* \" # closing quote # quoted strings )* < (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* # leading < (?: @ (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) # initial subdomain (?: # (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* \\. # if led by a period... (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) # ...further okay )* (?: (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* , (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* @ (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) # initial subdomain (?: # (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* \\. # if led by a period... (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) # ...further okay )* )* # further okay, if led by comma : # closing colon (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* )? # optional route (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \" (?: # opening quote... [^\\\\\\x80-\\xff\\n\\015\"] # Anything except backslash and quote | # or \\\\ [^\\x80-\\xff] # Escaped something (something != CR) )* \" # closing quote ) # initial word (?: (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* \\. (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \" (?: # opening quote... [^\\\\\\x80-\\xff\\n\\015\"] # Anything except backslash and quote | # or \\\\ [^\\x80-\\xff] # Escaped something (something != CR) )* \" # closing quote ) )* # further okay, if led by a period (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* @ (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) # initial subdomain (?: # (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* \\. # if led by a period... (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) # ...further okay )* # address spec (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* > # trailing > # name and address ) (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* # optional trailing comment /x" " (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* # optional leading comment (?: (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \" (?: # opening quote... [^\\\\\\x80-\\xff\\n\\015\"] # Anything except backslash and quote | # or \\\\ [^\\x80-\\xff] # Escaped something (something != CR) )* \" # closing quote ) # initial word (?: (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* \\. (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \" (?: # opening quote... [^\\\\\\x80-\\xff\\n\\015\"] # Anything except backslash and quote | # or \\\\ [^\\x80-\\xff] # Escaped something (something != CR) )* \" # closing quote ) )* # further okay, if led by a period (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* @ (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) # initial subdomain (?: # (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* \\. # if led by a period... (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) # ...further okay )* # address | # or (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \" (?: # opening quote... [^\\\\\\x80-\\xff\\n\\015\"] # Anything except backslash and quote | # or \\\\ [^\\x80-\\xff] # Escaped something (something != CR) )* \" # closing quote ) # one word, optionally followed by.... (?: [^()<>@,;:\".\\\\\\[\\]\\x80-\\xff\\000-\\010\\012-\\037] | # atom and space parts, or... \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) | # comments, or... \" (?: # opening quote... [^\\\\\\x80-\\xff\\n\\015\"] # Anything except backslash and quote | # or \\\\ [^\\x80-\\xff] # Escaped something (something != CR) )* \" # closing quote # quoted strings )* < (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* # leading < (?: @ (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) # initial subdomain (?: # (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* \\. # if led by a period... (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) # ...further okay )* (?: (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* , (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* @ (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) # initial subdomain (?: # (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* \\. # if led by a period... (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) # ...further okay )* )* # further okay, if led by comma : # closing colon (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* )? # optional route (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \" (?: # opening quote... [^\\\\\\x80-\\xff\\n\\015\"] # Anything except backslash and quote | # or \\\\ [^\\x80-\\xff] # Escaped something (something != CR) )* \" # closing quote ) # initial word (?: (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* \\. (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \" (?: # opening quote... [^\\\\\\x80-\\xff\\n\\015\"] # Anything except backslash and quote | # or \\\\ [^\\x80-\\xff] # Escaped something (something != CR) )* \" # closing quote ) )* # further okay, if led by a period (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* @ (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) # initial subdomain (?: # (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* \\. # if led by a period... (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) # ...further okay )* # address spec (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* > # trailing > # name and address ) (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* # optional trailing comment " nil nil nil t "user@dom.ain" nil "user@dom.ain" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (292 "\"\\\"A. Other\\\" (a comment)\" =~ / (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* # optional leading comment (?: (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \" (?: # opening quote... [^\\\\\\x80-\\xff\\n\\015\"] # Anything except backslash and quote | # or \\\\ [^\\x80-\\xff] # Escaped something (something != CR) )* \" # closing quote ) # initial word (?: (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* \\. (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \" (?: # opening quote... [^\\\\\\x80-\\xff\\n\\015\"] # Anything except backslash and quote | # or \\\\ [^\\x80-\\xff] # Escaped something (something != CR) )* \" # closing quote ) )* # further okay, if led by a period (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* @ (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) # initial subdomain (?: # (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* \\. # if led by a period... (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) # ...further okay )* # address | # or (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \" (?: # opening quote... [^\\\\\\x80-\\xff\\n\\015\"] # Anything except backslash and quote | # or \\\\ [^\\x80-\\xff] # Escaped something (something != CR) )* \" # closing quote ) # one word, optionally followed by.... (?: [^()<>@,;:\".\\\\\\[\\]\\x80-\\xff\\000-\\010\\012-\\037] | # atom and space parts, or... \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) | # comments, or... \" (?: # opening quote... [^\\\\\\x80-\\xff\\n\\015\"] # Anything except backslash and quote | # or \\\\ [^\\x80-\\xff] # Escaped something (something != CR) )* \" # closing quote # quoted strings )* < (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* # leading < (?: @ (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) # initial subdomain (?: # (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* \\. # if led by a period... (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) # ...further okay )* (?: (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* , (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* @ (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) # initial subdomain (?: # (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* \\. # if led by a period... (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) # ...further okay )* )* # further okay, if led by comma : # closing colon (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* )? # optional route (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \" (?: # opening quote... [^\\\\\\x80-\\xff\\n\\015\"] # Anything except backslash and quote | # or \\\\ [^\\x80-\\xff] # Escaped something (something != CR) )* \" # closing quote ) # initial word (?: (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* \\. (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \" (?: # opening quote... [^\\\\\\x80-\\xff\\n\\015\"] # Anything except backslash and quote | # or \\\\ [^\\x80-\\xff] # Escaped something (something != CR) )* \" # closing quote ) )* # further okay, if led by a period (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* @ (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) # initial subdomain (?: # (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* \\. # if led by a period... (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) # ...further okay )* # address spec (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* > # trailing > # name and address ) (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* # optional trailing comment /x" " (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* # optional leading comment (?: (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \" (?: # opening quote... [^\\\\\\x80-\\xff\\n\\015\"] # Anything except backslash and quote | # or \\\\ [^\\x80-\\xff] # Escaped something (something != CR) )* \" # closing quote ) # initial word (?: (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* \\. (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \" (?: # opening quote... [^\\\\\\x80-\\xff\\n\\015\"] # Anything except backslash and quote | # or \\\\ [^\\x80-\\xff] # Escaped something (something != CR) )* \" # closing quote ) )* # further okay, if led by a period (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* @ (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) # initial subdomain (?: # (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* \\. # if led by a period... (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) # ...further okay )* # address | # or (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \" (?: # opening quote... [^\\\\\\x80-\\xff\\n\\015\"] # Anything except backslash and quote | # or \\\\ [^\\x80-\\xff] # Escaped something (something != CR) )* \" # closing quote ) # one word, optionally followed by.... (?: [^()<>@,;:\".\\\\\\[\\]\\x80-\\xff\\000-\\010\\012-\\037] | # atom and space parts, or... \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) | # comments, or... \" (?: # opening quote... [^\\\\\\x80-\\xff\\n\\015\"] # Anything except backslash and quote | # or \\\\ [^\\x80-\\xff] # Escaped something (something != CR) )* \" # closing quote # quoted strings )* < (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* # leading < (?: @ (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) # initial subdomain (?: # (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* \\. # if led by a period... (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) # ...further okay )* (?: (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* , (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* @ (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) # initial subdomain (?: # (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* \\. # if led by a period... (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) # ...further okay )* )* # further okay, if led by comma : # closing colon (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* )? # optional route (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \" (?: # opening quote... [^\\\\\\x80-\\xff\\n\\015\"] # Anything except backslash and quote | # or \\\\ [^\\x80-\\xff] # Escaped something (something != CR) )* \" # closing quote ) # initial word (?: (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* \\. (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \" (?: # opening quote... [^\\\\\\x80-\\xff\\n\\015\"] # Anything except backslash and quote | # or \\\\ [^\\x80-\\xff] # Escaped something (something != CR) )* \" # closing quote ) )* # further okay, if led by a period (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* @ (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) # initial subdomain (?: # (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* \\. # if led by a period... (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) # ...further okay )* # address spec (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* > # trailing > # name and address ) (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* # optional trailing comment " nil nil nil t "\"A. Other\" (a comment)" nil "\"A. Other\" (a comment)" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (293 "\"A. Other (a comment)\" =~ / (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* # optional leading comment (?: (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \" (?: # opening quote... [^\\\\\\x80-\\xff\\n\\015\"] # Anything except backslash and quote | # or \\\\ [^\\x80-\\xff] # Escaped something (something != CR) )* \" # closing quote ) # initial word (?: (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* \\. (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \" (?: # opening quote... [^\\\\\\x80-\\xff\\n\\015\"] # Anything except backslash and quote | # or \\\\ [^\\x80-\\xff] # Escaped something (something != CR) )* \" # closing quote ) )* # further okay, if led by a period (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* @ (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) # initial subdomain (?: # (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* \\. # if led by a period... (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) # ...further okay )* # address | # or (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \" (?: # opening quote... [^\\\\\\x80-\\xff\\n\\015\"] # Anything except backslash and quote | # or \\\\ [^\\x80-\\xff] # Escaped something (something != CR) )* \" # closing quote ) # one word, optionally followed by.... (?: [^()<>@,;:\".\\\\\\[\\]\\x80-\\xff\\000-\\010\\012-\\037] | # atom and space parts, or... \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) | # comments, or... \" (?: # opening quote... [^\\\\\\x80-\\xff\\n\\015\"] # Anything except backslash and quote | # or \\\\ [^\\x80-\\xff] # Escaped something (something != CR) )* \" # closing quote # quoted strings )* < (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* # leading < (?: @ (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) # initial subdomain (?: # (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* \\. # if led by a period... (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) # ...further okay )* (?: (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* , (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* @ (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) # initial subdomain (?: # (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* \\. # if led by a period... (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) # ...further okay )* )* # further okay, if led by comma : # closing colon (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* )? # optional route (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \" (?: # opening quote... [^\\\\\\x80-\\xff\\n\\015\"] # Anything except backslash and quote | # or \\\\ [^\\x80-\\xff] # Escaped something (something != CR) )* \" # closing quote ) # initial word (?: (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* \\. (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \" (?: # opening quote... [^\\\\\\x80-\\xff\\n\\015\"] # Anything except backslash and quote | # or \\\\ [^\\x80-\\xff] # Escaped something (something != CR) )* \" # closing quote ) )* # further okay, if led by a period (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* @ (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) # initial subdomain (?: # (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* \\. # if led by a period... (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) # ...further okay )* # address spec (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* > # trailing > # name and address ) (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* # optional trailing comment /x" " (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* # optional leading comment (?: (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \" (?: # opening quote... [^\\\\\\x80-\\xff\\n\\015\"] # Anything except backslash and quote | # or \\\\ [^\\x80-\\xff] # Escaped something (something != CR) )* \" # closing quote ) # initial word (?: (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* \\. (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \" (?: # opening quote... [^\\\\\\x80-\\xff\\n\\015\"] # Anything except backslash and quote | # or \\\\ [^\\x80-\\xff] # Escaped something (something != CR) )* \" # closing quote ) )* # further okay, if led by a period (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* @ (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) # initial subdomain (?: # (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* \\. # if led by a period... (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) # ...further okay )* # address | # or (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \" (?: # opening quote... [^\\\\\\x80-\\xff\\n\\015\"] # Anything except backslash and quote | # or \\\\ [^\\x80-\\xff] # Escaped something (something != CR) )* \" # closing quote ) # one word, optionally followed by.... (?: [^()<>@,;:\".\\\\\\[\\]\\x80-\\xff\\000-\\010\\012-\\037] | # atom and space parts, or... \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) | # comments, or... \" (?: # opening quote... [^\\\\\\x80-\\xff\\n\\015\"] # Anything except backslash and quote | # or \\\\ [^\\x80-\\xff] # Escaped something (something != CR) )* \" # closing quote # quoted strings )* < (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* # leading < (?: @ (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) # initial subdomain (?: # (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* \\. # if led by a period... (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) # ...further okay )* (?: (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* , (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* @ (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) # initial subdomain (?: # (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* \\. # if led by a period... (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) # ...further okay )* )* # further okay, if led by comma : # closing colon (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* )? # optional route (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \" (?: # opening quote... [^\\\\\\x80-\\xff\\n\\015\"] # Anything except backslash and quote | # or \\\\ [^\\x80-\\xff] # Escaped something (something != CR) )* \" # closing quote ) # initial word (?: (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* \\. (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \" (?: # opening quote... [^\\\\\\x80-\\xff\\n\\015\"] # Anything except backslash and quote | # or \\\\ [^\\x80-\\xff] # Escaped something (something != CR) )* \" # closing quote ) )* # further okay, if led by a period (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* @ (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) # initial subdomain (?: # (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* \\. # if led by a period... (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) # ...further okay )* # address spec (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* > # trailing > # name and address ) (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* # optional trailing comment " nil nil nil t "A. Other (a comment)" nil " Other (a comment)" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (294 "\"\\\"/s=user/ou=host/o=place/prmd=uu.yy/admd= /c=gb/\\\"\\@x400-re.lay\" =~ / (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* # optional leading comment (?: (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \" (?: # opening quote... [^\\\\\\x80-\\xff\\n\\015\"] # Anything except backslash and quote | # or \\\\ [^\\x80-\\xff] # Escaped something (something != CR) )* \" # closing quote ) # initial word (?: (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* \\. (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \" (?: # opening quote... [^\\\\\\x80-\\xff\\n\\015\"] # Anything except backslash and quote | # or \\\\ [^\\x80-\\xff] # Escaped something (something != CR) )* \" # closing quote ) )* # further okay, if led by a period (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* @ (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) # initial subdomain (?: # (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* \\. # if led by a period... (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) # ...further okay )* # address | # or (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \" (?: # opening quote... [^\\\\\\x80-\\xff\\n\\015\"] # Anything except backslash and quote | # or \\\\ [^\\x80-\\xff] # Escaped something (something != CR) )* \" # closing quote ) # one word, optionally followed by.... (?: [^()<>@,;:\".\\\\\\[\\]\\x80-\\xff\\000-\\010\\012-\\037] | # atom and space parts, or... \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) | # comments, or... \" (?: # opening quote... [^\\\\\\x80-\\xff\\n\\015\"] # Anything except backslash and quote | # or \\\\ [^\\x80-\\xff] # Escaped something (something != CR) )* \" # closing quote # quoted strings )* < (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* # leading < (?: @ (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) # initial subdomain (?: # (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* \\. # if led by a period... (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) # ...further okay )* (?: (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* , (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* @ (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) # initial subdomain (?: # (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* \\. # if led by a period... (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) # ...further okay )* )* # further okay, if led by comma : # closing colon (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* )? # optional route (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \" (?: # opening quote... [^\\\\\\x80-\\xff\\n\\015\"] # Anything except backslash and quote | # or \\\\ [^\\x80-\\xff] # Escaped something (something != CR) )* \" # closing quote ) # initial word (?: (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* \\. (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \" (?: # opening quote... [^\\\\\\x80-\\xff\\n\\015\"] # Anything except backslash and quote | # or \\\\ [^\\x80-\\xff] # Escaped something (something != CR) )* \" # closing quote ) )* # further okay, if led by a period (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* @ (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) # initial subdomain (?: # (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* \\. # if led by a period... (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) # ...further okay )* # address spec (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* > # trailing > # name and address ) (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* # optional trailing comment /x" " (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* # optional leading comment (?: (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \" (?: # opening quote... [^\\\\\\x80-\\xff\\n\\015\"] # Anything except backslash and quote | # or \\\\ [^\\x80-\\xff] # Escaped something (something != CR) )* \" # closing quote ) # initial word (?: (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* \\. (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \" (?: # opening quote... [^\\\\\\x80-\\xff\\n\\015\"] # Anything except backslash and quote | # or \\\\ [^\\x80-\\xff] # Escaped something (something != CR) )* \" # closing quote ) )* # further okay, if led by a period (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* @ (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) # initial subdomain (?: # (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* \\. # if led by a period... (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) # ...further okay )* # address | # or (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \" (?: # opening quote... [^\\\\\\x80-\\xff\\n\\015\"] # Anything except backslash and quote | # or \\\\ [^\\x80-\\xff] # Escaped something (something != CR) )* \" # closing quote ) # one word, optionally followed by.... (?: [^()<>@,;:\".\\\\\\[\\]\\x80-\\xff\\000-\\010\\012-\\037] | # atom and space parts, or... \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) | # comments, or... \" (?: # opening quote... [^\\\\\\x80-\\xff\\n\\015\"] # Anything except backslash and quote | # or \\\\ [^\\x80-\\xff] # Escaped something (something != CR) )* \" # closing quote # quoted strings )* < (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* # leading < (?: @ (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) # initial subdomain (?: # (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* \\. # if led by a period... (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) # ...further okay )* (?: (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* , (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* @ (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) # initial subdomain (?: # (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* \\. # if led by a period... (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) # ...further okay )* )* # further okay, if led by comma : # closing colon (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* )? # optional route (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \" (?: # opening quote... [^\\\\\\x80-\\xff\\n\\015\"] # Anything except backslash and quote | # or \\\\ [^\\x80-\\xff] # Escaped something (something != CR) )* \" # closing quote ) # initial word (?: (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* \\. (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \" (?: # opening quote... [^\\\\\\x80-\\xff\\n\\015\"] # Anything except backslash and quote | # or \\\\ [^\\x80-\\xff] # Escaped something (something != CR) )* \" # closing quote ) )* # further okay, if led by a period (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* @ (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) # initial subdomain (?: # (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* \\. # if led by a period... (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) # ...further okay )* # address spec (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* > # trailing > # name and address ) (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* # optional trailing comment " nil nil nil t "\"/s=user/ou=host/o=place/prmd=uu.yy/admd= /c=gb/\"@x400-re.lay" nil "\"/s=user/ou=host/o=place/prmd=uu.yy/admd= /c=gb/\"@x400-re.lay" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (295 "\"A missing angle @,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \" (?: # opening quote... [^\\\\\\x80-\\xff\\n\\015\"] # Anything except backslash and quote | # or \\\\ [^\\x80-\\xff] # Escaped something (something != CR) )* \" # closing quote ) # initial word (?: (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* \\. (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \" (?: # opening quote... [^\\\\\\x80-\\xff\\n\\015\"] # Anything except backslash and quote | # or \\\\ [^\\x80-\\xff] # Escaped something (something != CR) )* \" # closing quote ) )* # further okay, if led by a period (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* @ (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) # initial subdomain (?: # (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* \\. # if led by a period... (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) # ...further okay )* # address | # or (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \" (?: # opening quote... [^\\\\\\x80-\\xff\\n\\015\"] # Anything except backslash and quote | # or \\\\ [^\\x80-\\xff] # Escaped something (something != CR) )* \" # closing quote ) # one word, optionally followed by.... (?: [^()<>@,;:\".\\\\\\[\\]\\x80-\\xff\\000-\\010\\012-\\037] | # atom and space parts, or... \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) | # comments, or... \" (?: # opening quote... [^\\\\\\x80-\\xff\\n\\015\"] # Anything except backslash and quote | # or \\\\ [^\\x80-\\xff] # Escaped something (something != CR) )* \" # closing quote # quoted strings )* < (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* # leading < (?: @ (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) # initial subdomain (?: # (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* \\. # if led by a period... (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) # ...further okay )* (?: (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* , (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* @ (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) # initial subdomain (?: # (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* \\. # if led by a period... (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) # ...further okay )* )* # further okay, if led by comma : # closing colon (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* )? # optional route (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \" (?: # opening quote... [^\\\\\\x80-\\xff\\n\\015\"] # Anything except backslash and quote | # or \\\\ [^\\x80-\\xff] # Escaped something (something != CR) )* \" # closing quote ) # initial word (?: (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* \\. (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \" (?: # opening quote... [^\\\\\\x80-\\xff\\n\\015\"] # Anything except backslash and quote | # or \\\\ [^\\x80-\\xff] # Escaped something (something != CR) )* \" # closing quote ) )* # further okay, if led by a period (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* @ (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) # initial subdomain (?: # (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* \\. # if led by a period... (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) # ...further okay )* # address spec (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* > # trailing > # name and address ) (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* # optional trailing comment /x" " (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* # optional leading comment (?: (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \" (?: # opening quote... [^\\\\\\x80-\\xff\\n\\015\"] # Anything except backslash and quote | # or \\\\ [^\\x80-\\xff] # Escaped something (something != CR) )* \" # closing quote ) # initial word (?: (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* \\. (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \" (?: # opening quote... [^\\\\\\x80-\\xff\\n\\015\"] # Anything except backslash and quote | # or \\\\ [^\\x80-\\xff] # Escaped something (something != CR) )* \" # closing quote ) )* # further okay, if led by a period (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* @ (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) # initial subdomain (?: # (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* \\. # if led by a period... (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) # ...further okay )* # address | # or (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \" (?: # opening quote... [^\\\\\\x80-\\xff\\n\\015\"] # Anything except backslash and quote | # or \\\\ [^\\x80-\\xff] # Escaped something (something != CR) )* \" # closing quote ) # one word, optionally followed by.... (?: [^()<>@,;:\".\\\\\\[\\]\\x80-\\xff\\000-\\010\\012-\\037] | # atom and space parts, or... \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) | # comments, or... \" (?: # opening quote... [^\\\\\\x80-\\xff\\n\\015\"] # Anything except backslash and quote | # or \\\\ [^\\x80-\\xff] # Escaped something (something != CR) )* \" # closing quote # quoted strings )* < (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* # leading < (?: @ (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) # initial subdomain (?: # (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* \\. # if led by a period... (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) # ...further okay )* (?: (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* , (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* @ (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) # initial subdomain (?: # (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* \\. # if led by a period... (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) # ...further okay )* )* # further okay, if led by comma : # closing colon (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* )? # optional route (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \" (?: # opening quote... [^\\\\\\x80-\\xff\\n\\015\"] # Anything except backslash and quote | # or \\\\ [^\\x80-\\xff] # Escaped something (something != CR) )* \" # closing quote ) # initial word (?: (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* \\. (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \" (?: # opening quote... [^\\\\\\x80-\\xff\\n\\015\"] # Anything except backslash and quote | # or \\\\ [^\\x80-\\xff] # Escaped something (something != CR) )* \" # closing quote ) )* # further okay, if led by a period (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* @ (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) # initial subdomain (?: # (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* \\. # if led by a period... (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) # ...further okay )* # address spec (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* > # trailing > # name and address ) (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* # optional trailing comment " nil nil nil t "A missing angle @,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \" (?: # opening quote... [^\\\\\\x80-\\xff\\n\\015\"] # Anything except backslash and quote | # or \\\\ [^\\x80-\\xff] # Escaped something (something != CR) )* \" # closing quote ) # initial word (?: (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* \\. (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \" (?: # opening quote... [^\\\\\\x80-\\xff\\n\\015\"] # Anything except backslash and quote | # or \\\\ [^\\x80-\\xff] # Escaped something (something != CR) )* \" # closing quote ) )* # further okay, if led by a period (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* @ (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) # initial subdomain (?: # (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* \\. # if led by a period... (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) # ...further okay )* # address | # or (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \" (?: # opening quote... [^\\\\\\x80-\\xff\\n\\015\"] # Anything except backslash and quote | # or \\\\ [^\\x80-\\xff] # Escaped something (something != CR) )* \" # closing quote ) # one word, optionally followed by.... (?: [^()<>@,;:\".\\\\\\[\\]\\x80-\\xff\\000-\\010\\012-\\037] | # atom and space parts, or... \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) | # comments, or... \" (?: # opening quote... [^\\\\\\x80-\\xff\\n\\015\"] # Anything except backslash and quote | # or \\\\ [^\\x80-\\xff] # Escaped something (something != CR) )* \" # closing quote # quoted strings )* < (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* # leading < (?: @ (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) # initial subdomain (?: # (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* \\. # if led by a period... (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) # ...further okay )* (?: (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* , (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* @ (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) # initial subdomain (?: # (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* \\. # if led by a period... (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) # ...further okay )* )* # further okay, if led by comma : # closing colon (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* )? # optional route (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \" (?: # opening quote... [^\\\\\\x80-\\xff\\n\\015\"] # Anything except backslash and quote | # or \\\\ [^\\x80-\\xff] # Escaped something (something != CR) )* \" # closing quote ) # initial word (?: (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* \\. (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \" (?: # opening quote... [^\\\\\\x80-\\xff\\n\\015\"] # Anything except backslash and quote | # or \\\\ [^\\x80-\\xff] # Escaped something (something != CR) )* \" # closing quote ) )* # further okay, if led by a period (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* @ (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) # initial subdomain (?: # (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* \\. # if led by a period... (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) # ...further okay )* # address spec (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* > # trailing > # name and address ) (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* # optional trailing comment /x" " (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* # optional leading comment (?: (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \" (?: # opening quote... [^\\\\\\x80-\\xff\\n\\015\"] # Anything except backslash and quote | # or \\\\ [^\\x80-\\xff] # Escaped something (something != CR) )* \" # closing quote ) # initial word (?: (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* \\. (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \" (?: # opening quote... [^\\\\\\x80-\\xff\\n\\015\"] # Anything except backslash and quote | # or \\\\ [^\\x80-\\xff] # Escaped something (something != CR) )* \" # closing quote ) )* # further okay, if led by a period (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* @ (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) # initial subdomain (?: # (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* \\. # if led by a period... (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) # ...further okay )* # address | # or (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \" (?: # opening quote... [^\\\\\\x80-\\xff\\n\\015\"] # Anything except backslash and quote | # or \\\\ [^\\x80-\\xff] # Escaped something (something != CR) )* \" # closing quote ) # one word, optionally followed by.... (?: [^()<>@,;:\".\\\\\\[\\]\\x80-\\xff\\000-\\010\\012-\\037] | # atom and space parts, or... \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) | # comments, or... \" (?: # opening quote... [^\\\\\\x80-\\xff\\n\\015\"] # Anything except backslash and quote | # or \\\\ [^\\x80-\\xff] # Escaped something (something != CR) )* \" # closing quote # quoted strings )* < (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* # leading < (?: @ (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) # initial subdomain (?: # (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* \\. # if led by a period... (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) # ...further okay )* (?: (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* , (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* @ (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) # initial subdomain (?: # (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* \\. # if led by a period... (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) # ...further okay )* )* # further okay, if led by comma : # closing colon (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* )? # optional route (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \" (?: # opening quote... [^\\\\\\x80-\\xff\\n\\015\"] # Anything except backslash and quote | # or \\\\ [^\\x80-\\xff] # Escaped something (something != CR) )* \" # closing quote ) # initial word (?: (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* \\. (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \" (?: # opening quote... [^\\\\\\x80-\\xff\\n\\015\"] # Anything except backslash and quote | # or \\\\ [^\\x80-\\xff] # Escaped something (something != CR) )* \" # closing quote ) )* # further okay, if led by a period (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* @ (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) # initial subdomain (?: # (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* \\. # if led by a period... (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) # ...further okay )* # address spec (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* > # trailing > # name and address ) (?: [\\040\\t] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] | \\( (?: [^\\\\\\x80-\\xff\\n\\015()] | \\\\ [^\\x80-\\xff] )* \\) )* \\) )* # optional trailing comment " nil nil nil t "The quick brown fox" nil nil nil) (297 "\"Alan Other \" =~ /[\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional leading comment (?: (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom # Atom | # or \" # \" [^\\\\\\x80-\\xff\\n\\015\"] * # normal (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015\"] * )* # ( special normal* )* \" # \" # Quoted string ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: \\. [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom # Atom | # or \" # \" [^\\\\\\x80-\\xff\\n\\015\"] * # normal (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015\"] * )* # ( special normal* )* \" # \" # Quoted string ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # additional words )* @ [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional trailing comments (?: \\. [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional trailing comments )* # address | # or (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom # Atom | # or \" # \" [^\\\\\\x80-\\xff\\n\\015\"] * # normal (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015\"] * )* # ( special normal* )* \" # \" # Quoted string ) # leading word [^()<>@,;:\".\\\\\\[\\]\\x80-\\xff\\000-\\010\\012-\\037] * # \"normal\" atoms and or spaces (?: (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) | \" # \" [^\\\\\\x80-\\xff\\n\\015\"] * # normal (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015\"] * )* # ( special normal* )* \" # \" ) # \"special\" comment or quoted string [^()<>@,;:\".\\\\\\[\\]\\x80-\\xff\\000-\\010\\012-\\037] * # more \"normal\" )* < [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # < (?: @ [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional trailing comments (?: \\. [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional trailing comments )* (?: , [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. @ [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional trailing comments (?: \\. [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional trailing comments )* )* # additional domains : [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional trailing comments )? # optional route (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom # Atom | # or \" # \" [^\\\\\\x80-\\xff\\n\\015\"] * # normal (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015\"] * )* # ( special normal* )* \" # \" # Quoted string ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: \\. [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom # Atom | # or \" # \" [^\\\\\\x80-\\xff\\n\\015\"] * # normal (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015\"] * )* # ( special normal* )* \" # \" # Quoted string ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # additional words )* @ [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional trailing comments (?: \\. [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional trailing comments )* # address spec > # > # name and address ) /x" "[\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional leading comment (?: (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom # Atom | # or \" # \" [^\\\\\\x80-\\xff\\n\\015\"] * # normal (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015\"] * )* # ( special normal* )* \" # \" # Quoted string ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: \\. [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom # Atom | # or \" # \" [^\\\\\\x80-\\xff\\n\\015\"] * # normal (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015\"] * )* # ( special normal* )* \" # \" # Quoted string ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # additional words )* @ [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional trailing comments (?: \\. [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional trailing comments )* # address | # or (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom # Atom | # or \" # \" [^\\\\\\x80-\\xff\\n\\015\"] * # normal (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015\"] * )* # ( special normal* )* \" # \" # Quoted string ) # leading word [^()<>@,;:\".\\\\\\[\\]\\x80-\\xff\\000-\\010\\012-\\037] * # \"normal\" atoms and or spaces (?: (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) | \" # \" [^\\\\\\x80-\\xff\\n\\015\"] * # normal (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015\"] * )* # ( special normal* )* \" # \" ) # \"special\" comment or quoted string [^()<>@,;:\".\\\\\\[\\]\\x80-\\xff\\000-\\010\\012-\\037] * # more \"normal\" )* < [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # < (?: @ [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional trailing comments (?: \\. [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional trailing comments )* (?: , [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. @ [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional trailing comments (?: \\. [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional trailing comments )* )* # additional domains : [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional trailing comments )? # optional route (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom # Atom | # or \" # \" [^\\\\\\x80-\\xff\\n\\015\"] * # normal (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015\"] * )* # ( special normal* )* \" # \" # Quoted string ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: \\. [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom # Atom | # or \" # \" [^\\\\\\x80-\\xff\\n\\015\"] * # normal (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015\"] * )* # ( special normal* )* \" # \" # Quoted string ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # additional words )* @ [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional trailing comments (?: \\. [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional trailing comments )* # address spec > # > # name and address ) " nil nil nil t "Alan Other " nil "Alan Other " (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (298 "\"\" =~ /[\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional leading comment (?: (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom # Atom | # or \" # \" [^\\\\\\x80-\\xff\\n\\015\"] * # normal (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015\"] * )* # ( special normal* )* \" # \" # Quoted string ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: \\. [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom # Atom | # or \" # \" [^\\\\\\x80-\\xff\\n\\015\"] * # normal (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015\"] * )* # ( special normal* )* \" # \" # Quoted string ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # additional words )* @ [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional trailing comments (?: \\. [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional trailing comments )* # address | # or (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom # Atom | # or \" # \" [^\\\\\\x80-\\xff\\n\\015\"] * # normal (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015\"] * )* # ( special normal* )* \" # \" # Quoted string ) # leading word [^()<>@,;:\".\\\\\\[\\]\\x80-\\xff\\000-\\010\\012-\\037] * # \"normal\" atoms and or spaces (?: (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) | \" # \" [^\\\\\\x80-\\xff\\n\\015\"] * # normal (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015\"] * )* # ( special normal* )* \" # \" ) # \"special\" comment or quoted string [^()<>@,;:\".\\\\\\[\\]\\x80-\\xff\\000-\\010\\012-\\037] * # more \"normal\" )* < [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # < (?: @ [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional trailing comments (?: \\. [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional trailing comments )* (?: , [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. @ [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional trailing comments (?: \\. [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional trailing comments )* )* # additional domains : [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional trailing comments )? # optional route (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom # Atom | # or \" # \" [^\\\\\\x80-\\xff\\n\\015\"] * # normal (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015\"] * )* # ( special normal* )* \" # \" # Quoted string ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: \\. [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom # Atom | # or \" # \" [^\\\\\\x80-\\xff\\n\\015\"] * # normal (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015\"] * )* # ( special normal* )* \" # \" # Quoted string ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # additional words )* @ [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional trailing comments (?: \\. [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional trailing comments )* # address spec > # > # name and address ) /x" "[\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional leading comment (?: (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom # Atom | # or \" # \" [^\\\\\\x80-\\xff\\n\\015\"] * # normal (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015\"] * )* # ( special normal* )* \" # \" # Quoted string ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: \\. [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom # Atom | # or \" # \" [^\\\\\\x80-\\xff\\n\\015\"] * # normal (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015\"] * )* # ( special normal* )* \" # \" # Quoted string ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # additional words )* @ [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional trailing comments (?: \\. [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional trailing comments )* # address | # or (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom # Atom | # or \" # \" [^\\\\\\x80-\\xff\\n\\015\"] * # normal (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015\"] * )* # ( special normal* )* \" # \" # Quoted string ) # leading word [^()<>@,;:\".\\\\\\[\\]\\x80-\\xff\\000-\\010\\012-\\037] * # \"normal\" atoms and or spaces (?: (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) | \" # \" [^\\\\\\x80-\\xff\\n\\015\"] * # normal (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015\"] * )* # ( special normal* )* \" # \" ) # \"special\" comment or quoted string [^()<>@,;:\".\\\\\\[\\]\\x80-\\xff\\000-\\010\\012-\\037] * # more \"normal\" )* < [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # < (?: @ [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional trailing comments (?: \\. [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional trailing comments )* (?: , [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. @ [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional trailing comments (?: \\. [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional trailing comments )* )* # additional domains : [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional trailing comments )? # optional route (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom # Atom | # or \" # \" [^\\\\\\x80-\\xff\\n\\015\"] * # normal (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015\"] * )* # ( special normal* )* \" # \" # Quoted string ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: \\. [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom # Atom | # or \" # \" [^\\\\\\x80-\\xff\\n\\015\"] * # normal (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015\"] * )* # ( special normal* )* \" # \" # Quoted string ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # additional words )* @ [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional trailing comments (?: \\. [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional trailing comments )* # address spec > # > # name and address ) " nil nil nil t "" nil "user@dom.ain" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (299 "\"user\\@dom.ain\" =~ /[\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional leading comment (?: (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom # Atom | # or \" # \" [^\\\\\\x80-\\xff\\n\\015\"] * # normal (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015\"] * )* # ( special normal* )* \" # \" # Quoted string ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: \\. [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom # Atom | # or \" # \" [^\\\\\\x80-\\xff\\n\\015\"] * # normal (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015\"] * )* # ( special normal* )* \" # \" # Quoted string ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # additional words )* @ [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional trailing comments (?: \\. [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional trailing comments )* # address | # or (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom # Atom | # or \" # \" [^\\\\\\x80-\\xff\\n\\015\"] * # normal (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015\"] * )* # ( special normal* )* \" # \" # Quoted string ) # leading word [^()<>@,;:\".\\\\\\[\\]\\x80-\\xff\\000-\\010\\012-\\037] * # \"normal\" atoms and or spaces (?: (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) | \" # \" [^\\\\\\x80-\\xff\\n\\015\"] * # normal (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015\"] * )* # ( special normal* )* \" # \" ) # \"special\" comment or quoted string [^()<>@,;:\".\\\\\\[\\]\\x80-\\xff\\000-\\010\\012-\\037] * # more \"normal\" )* < [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # < (?: @ [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional trailing comments (?: \\. [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional trailing comments )* (?: , [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. @ [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional trailing comments (?: \\. [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional trailing comments )* )* # additional domains : [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional trailing comments )? # optional route (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom # Atom | # or \" # \" [^\\\\\\x80-\\xff\\n\\015\"] * # normal (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015\"] * )* # ( special normal* )* \" # \" # Quoted string ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: \\. [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom # Atom | # or \" # \" [^\\\\\\x80-\\xff\\n\\015\"] * # normal (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015\"] * )* # ( special normal* )* \" # \" # Quoted string ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # additional words )* @ [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional trailing comments (?: \\. [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional trailing comments )* # address spec > # > # name and address ) /x" "[\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional leading comment (?: (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom # Atom | # or \" # \" [^\\\\\\x80-\\xff\\n\\015\"] * # normal (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015\"] * )* # ( special normal* )* \" # \" # Quoted string ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: \\. [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom # Atom | # or \" # \" [^\\\\\\x80-\\xff\\n\\015\"] * # normal (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015\"] * )* # ( special normal* )* \" # \" # Quoted string ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # additional words )* @ [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional trailing comments (?: \\. [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional trailing comments )* # address | # or (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom # Atom | # or \" # \" [^\\\\\\x80-\\xff\\n\\015\"] * # normal (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015\"] * )* # ( special normal* )* \" # \" # Quoted string ) # leading word [^()<>@,;:\".\\\\\\[\\]\\x80-\\xff\\000-\\010\\012-\\037] * # \"normal\" atoms and or spaces (?: (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) | \" # \" [^\\\\\\x80-\\xff\\n\\015\"] * # normal (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015\"] * )* # ( special normal* )* \" # \" ) # \"special\" comment or quoted string [^()<>@,;:\".\\\\\\[\\]\\x80-\\xff\\000-\\010\\012-\\037] * # more \"normal\" )* < [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # < (?: @ [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional trailing comments (?: \\. [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional trailing comments )* (?: , [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. @ [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional trailing comments (?: \\. [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional trailing comments )* )* # additional domains : [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional trailing comments )? # optional route (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom # Atom | # or \" # \" [^\\\\\\x80-\\xff\\n\\015\"] * # normal (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015\"] * )* # ( special normal* )* \" # \" # Quoted string ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: \\. [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom # Atom | # or \" # \" [^\\\\\\x80-\\xff\\n\\015\"] * # normal (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015\"] * )* # ( special normal* )* \" # \" # Quoted string ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # additional words )* @ [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional trailing comments (?: \\. [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional trailing comments )* # address spec > # > # name and address ) " nil nil nil t "user@dom.ain" nil "user@dom.ain" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (300 "\"\\\"A. Other\\\" (a comment)\" =~ /[\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional leading comment (?: (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom # Atom | # or \" # \" [^\\\\\\x80-\\xff\\n\\015\"] * # normal (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015\"] * )* # ( special normal* )* \" # \" # Quoted string ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: \\. [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom # Atom | # or \" # \" [^\\\\\\x80-\\xff\\n\\015\"] * # normal (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015\"] * )* # ( special normal* )* \" # \" # Quoted string ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # additional words )* @ [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional trailing comments (?: \\. [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional trailing comments )* # address | # or (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom # Atom | # or \" # \" [^\\\\\\x80-\\xff\\n\\015\"] * # normal (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015\"] * )* # ( special normal* )* \" # \" # Quoted string ) # leading word [^()<>@,;:\".\\\\\\[\\]\\x80-\\xff\\000-\\010\\012-\\037] * # \"normal\" atoms and or spaces (?: (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) | \" # \" [^\\\\\\x80-\\xff\\n\\015\"] * # normal (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015\"] * )* # ( special normal* )* \" # \" ) # \"special\" comment or quoted string [^()<>@,;:\".\\\\\\[\\]\\x80-\\xff\\000-\\010\\012-\\037] * # more \"normal\" )* < [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # < (?: @ [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional trailing comments (?: \\. [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional trailing comments )* (?: , [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. @ [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional trailing comments (?: \\. [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional trailing comments )* )* # additional domains : [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional trailing comments )? # optional route (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom # Atom | # or \" # \" [^\\\\\\x80-\\xff\\n\\015\"] * # normal (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015\"] * )* # ( special normal* )* \" # \" # Quoted string ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: \\. [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom # Atom | # or \" # \" [^\\\\\\x80-\\xff\\n\\015\"] * # normal (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015\"] * )* # ( special normal* )* \" # \" # Quoted string ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # additional words )* @ [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional trailing comments (?: \\. [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional trailing comments )* # address spec > # > # name and address ) /x" "[\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional leading comment (?: (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom # Atom | # or \" # \" [^\\\\\\x80-\\xff\\n\\015\"] * # normal (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015\"] * )* # ( special normal* )* \" # \" # Quoted string ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: \\. [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom # Atom | # or \" # \" [^\\\\\\x80-\\xff\\n\\015\"] * # normal (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015\"] * )* # ( special normal* )* \" # \" # Quoted string ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # additional words )* @ [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional trailing comments (?: \\. [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional trailing comments )* # address | # or (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom # Atom | # or \" # \" [^\\\\\\x80-\\xff\\n\\015\"] * # normal (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015\"] * )* # ( special normal* )* \" # \" # Quoted string ) # leading word [^()<>@,;:\".\\\\\\[\\]\\x80-\\xff\\000-\\010\\012-\\037] * # \"normal\" atoms and or spaces (?: (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) | \" # \" [^\\\\\\x80-\\xff\\n\\015\"] * # normal (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015\"] * )* # ( special normal* )* \" # \" ) # \"special\" comment or quoted string [^()<>@,;:\".\\\\\\[\\]\\x80-\\xff\\000-\\010\\012-\\037] * # more \"normal\" )* < [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # < (?: @ [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional trailing comments (?: \\. [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional trailing comments )* (?: , [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. @ [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional trailing comments (?: \\. [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional trailing comments )* )* # additional domains : [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional trailing comments )? # optional route (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom # Atom | # or \" # \" [^\\\\\\x80-\\xff\\n\\015\"] * # normal (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015\"] * )* # ( special normal* )* \" # \" # Quoted string ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: \\. [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom # Atom | # or \" # \" [^\\\\\\x80-\\xff\\n\\015\"] * # normal (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015\"] * )* # ( special normal* )* \" # \" # Quoted string ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # additional words )* @ [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional trailing comments (?: \\. [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional trailing comments )* # address spec > # > # name and address ) " nil nil nil t "\"A. Other\" (a comment)" nil "\"A. Other\" " (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (301 "\"A. Other (a comment)\" =~ /[\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional leading comment (?: (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom # Atom | # or \" # \" [^\\\\\\x80-\\xff\\n\\015\"] * # normal (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015\"] * )* # ( special normal* )* \" # \" # Quoted string ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: \\. [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom # Atom | # or \" # \" [^\\\\\\x80-\\xff\\n\\015\"] * # normal (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015\"] * )* # ( special normal* )* \" # \" # Quoted string ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # additional words )* @ [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional trailing comments (?: \\. [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional trailing comments )* # address | # or (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom # Atom | # or \" # \" [^\\\\\\x80-\\xff\\n\\015\"] * # normal (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015\"] * )* # ( special normal* )* \" # \" # Quoted string ) # leading word [^()<>@,;:\".\\\\\\[\\]\\x80-\\xff\\000-\\010\\012-\\037] * # \"normal\" atoms and or spaces (?: (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) | \" # \" [^\\\\\\x80-\\xff\\n\\015\"] * # normal (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015\"] * )* # ( special normal* )* \" # \" ) # \"special\" comment or quoted string [^()<>@,;:\".\\\\\\[\\]\\x80-\\xff\\000-\\010\\012-\\037] * # more \"normal\" )* < [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # < (?: @ [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional trailing comments (?: \\. [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional trailing comments )* (?: , [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. @ [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional trailing comments (?: \\. [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional trailing comments )* )* # additional domains : [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional trailing comments )? # optional route (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom # Atom | # or \" # \" [^\\\\\\x80-\\xff\\n\\015\"] * # normal (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015\"] * )* # ( special normal* )* \" # \" # Quoted string ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: \\. [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom # Atom | # or \" # \" [^\\\\\\x80-\\xff\\n\\015\"] * # normal (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015\"] * )* # ( special normal* )* \" # \" # Quoted string ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # additional words )* @ [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional trailing comments (?: \\. [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional trailing comments )* # address spec > # > # name and address ) /x" "[\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional leading comment (?: (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom # Atom | # or \" # \" [^\\\\\\x80-\\xff\\n\\015\"] * # normal (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015\"] * )* # ( special normal* )* \" # \" # Quoted string ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: \\. [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom # Atom | # or \" # \" [^\\\\\\x80-\\xff\\n\\015\"] * # normal (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015\"] * )* # ( special normal* )* \" # \" # Quoted string ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # additional words )* @ [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional trailing comments (?: \\. [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional trailing comments )* # address | # or (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom # Atom | # or \" # \" [^\\\\\\x80-\\xff\\n\\015\"] * # normal (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015\"] * )* # ( special normal* )* \" # \" # Quoted string ) # leading word [^()<>@,;:\".\\\\\\[\\]\\x80-\\xff\\000-\\010\\012-\\037] * # \"normal\" atoms and or spaces (?: (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) | \" # \" [^\\\\\\x80-\\xff\\n\\015\"] * # normal (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015\"] * )* # ( special normal* )* \" # \" ) # \"special\" comment or quoted string [^()<>@,;:\".\\\\\\[\\]\\x80-\\xff\\000-\\010\\012-\\037] * # more \"normal\" )* < [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # < (?: @ [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional trailing comments (?: \\. [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional trailing comments )* (?: , [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. @ [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional trailing comments (?: \\. [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional trailing comments )* )* # additional domains : [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional trailing comments )? # optional route (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom # Atom | # or \" # \" [^\\\\\\x80-\\xff\\n\\015\"] * # normal (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015\"] * )* # ( special normal* )* \" # \" # Quoted string ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: \\. [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom # Atom | # or \" # \" [^\\\\\\x80-\\xff\\n\\015\"] * # normal (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015\"] * )* # ( special normal* )* \" # \" # Quoted string ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # additional words )* @ [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional trailing comments (?: \\. [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional trailing comments )* # address spec > # > # name and address ) " nil nil nil t "A. Other (a comment)" nil " Other " (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (302 "\"\\\"/s=user/ou=host/o=place/prmd=uu.yy/admd= /c=gb/\\\"\\@x400-re.lay\" =~ /[\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional leading comment (?: (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom # Atom | # or \" # \" [^\\\\\\x80-\\xff\\n\\015\"] * # normal (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015\"] * )* # ( special normal* )* \" # \" # Quoted string ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: \\. [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom # Atom | # or \" # \" [^\\\\\\x80-\\xff\\n\\015\"] * # normal (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015\"] * )* # ( special normal* )* \" # \" # Quoted string ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # additional words )* @ [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional trailing comments (?: \\. [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional trailing comments )* # address | # or (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom # Atom | # or \" # \" [^\\\\\\x80-\\xff\\n\\015\"] * # normal (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015\"] * )* # ( special normal* )* \" # \" # Quoted string ) # leading word [^()<>@,;:\".\\\\\\[\\]\\x80-\\xff\\000-\\010\\012-\\037] * # \"normal\" atoms and or spaces (?: (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) | \" # \" [^\\\\\\x80-\\xff\\n\\015\"] * # normal (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015\"] * )* # ( special normal* )* \" # \" ) # \"special\" comment or quoted string [^()<>@,;:\".\\\\\\[\\]\\x80-\\xff\\000-\\010\\012-\\037] * # more \"normal\" )* < [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # < (?: @ [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional trailing comments (?: \\. [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional trailing comments )* (?: , [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. @ [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional trailing comments (?: \\. [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional trailing comments )* )* # additional domains : [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional trailing comments )? # optional route (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom # Atom | # or \" # \" [^\\\\\\x80-\\xff\\n\\015\"] * # normal (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015\"] * )* # ( special normal* )* \" # \" # Quoted string ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: \\. [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom # Atom | # or \" # \" [^\\\\\\x80-\\xff\\n\\015\"] * # normal (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015\"] * )* # ( special normal* )* \" # \" # Quoted string ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # additional words )* @ [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional trailing comments (?: \\. [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional trailing comments )* # address spec > # > # name and address ) /x" "[\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional leading comment (?: (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom # Atom | # or \" # \" [^\\\\\\x80-\\xff\\n\\015\"] * # normal (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015\"] * )* # ( special normal* )* \" # \" # Quoted string ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: \\. [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom # Atom | # or \" # \" [^\\\\\\x80-\\xff\\n\\015\"] * # normal (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015\"] * )* # ( special normal* )* \" # \" # Quoted string ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # additional words )* @ [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional trailing comments (?: \\. [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional trailing comments )* # address | # or (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom # Atom | # or \" # \" [^\\\\\\x80-\\xff\\n\\015\"] * # normal (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015\"] * )* # ( special normal* )* \" # \" # Quoted string ) # leading word [^()<>@,;:\".\\\\\\[\\]\\x80-\\xff\\000-\\010\\012-\\037] * # \"normal\" atoms and or spaces (?: (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) | \" # \" [^\\\\\\x80-\\xff\\n\\015\"] * # normal (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015\"] * )* # ( special normal* )* \" # \" ) # \"special\" comment or quoted string [^()<>@,;:\".\\\\\\[\\]\\x80-\\xff\\000-\\010\\012-\\037] * # more \"normal\" )* < [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # < (?: @ [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional trailing comments (?: \\. [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional trailing comments )* (?: , [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. @ [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional trailing comments (?: \\. [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional trailing comments )* )* # additional domains : [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional trailing comments )? # optional route (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom # Atom | # or \" # \" [^\\\\\\x80-\\xff\\n\\015\"] * # normal (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015\"] * )* # ( special normal* )* \" # \" # Quoted string ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: \\. [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom # Atom | # or \" # \" [^\\\\\\x80-\\xff\\n\\015\"] * # normal (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015\"] * )* # ( special normal* )* \" # \" # Quoted string ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # additional words )* @ [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional trailing comments (?: \\. [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional trailing comments )* # address spec > # > # name and address ) " nil nil nil t "\"/s=user/ou=host/o=place/prmd=uu.yy/admd= /c=gb/\"@x400-re.lay" nil "\"/s=user/ou=host/o=place/prmd=uu.yy/admd= /c=gb/\"@x400-re.lay" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (303 "\"A missing angle @,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom # Atom | # or \" # \" [^\\\\\\x80-\\xff\\n\\015\"] * # normal (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015\"] * )* # ( special normal* )* \" # \" # Quoted string ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: \\. [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom # Atom | # or \" # \" [^\\\\\\x80-\\xff\\n\\015\"] * # normal (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015\"] * )* # ( special normal* )* \" # \" # Quoted string ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # additional words )* @ [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional trailing comments (?: \\. [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional trailing comments )* # address | # or (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom # Atom | # or \" # \" [^\\\\\\x80-\\xff\\n\\015\"] * # normal (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015\"] * )* # ( special normal* )* \" # \" # Quoted string ) # leading word [^()<>@,;:\".\\\\\\[\\]\\x80-\\xff\\000-\\010\\012-\\037] * # \"normal\" atoms and or spaces (?: (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) | \" # \" [^\\\\\\x80-\\xff\\n\\015\"] * # normal (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015\"] * )* # ( special normal* )* \" # \" ) # \"special\" comment or quoted string [^()<>@,;:\".\\\\\\[\\]\\x80-\\xff\\000-\\010\\012-\\037] * # more \"normal\" )* < [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # < (?: @ [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional trailing comments (?: \\. [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional trailing comments )* (?: , [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. @ [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional trailing comments (?: \\. [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional trailing comments )* )* # additional domains : [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional trailing comments )? # optional route (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom # Atom | # or \" # \" [^\\\\\\x80-\\xff\\n\\015\"] * # normal (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015\"] * )* # ( special normal* )* \" # \" # Quoted string ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: \\. [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom # Atom | # or \" # \" [^\\\\\\x80-\\xff\\n\\015\"] * # normal (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015\"] * )* # ( special normal* )* \" # \" # Quoted string ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # additional words )* @ [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional trailing comments (?: \\. [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional trailing comments )* # address spec > # > # name and address ) /x" "[\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional leading comment (?: (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom # Atom | # or \" # \" [^\\\\\\x80-\\xff\\n\\015\"] * # normal (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015\"] * )* # ( special normal* )* \" # \" # Quoted string ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: \\. [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom # Atom | # or \" # \" [^\\\\\\x80-\\xff\\n\\015\"] * # normal (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015\"] * )* # ( special normal* )* \" # \" # Quoted string ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # additional words )* @ [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional trailing comments (?: \\. [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional trailing comments )* # address | # or (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom # Atom | # or \" # \" [^\\\\\\x80-\\xff\\n\\015\"] * # normal (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015\"] * )* # ( special normal* )* \" # \" # Quoted string ) # leading word [^()<>@,;:\".\\\\\\[\\]\\x80-\\xff\\000-\\010\\012-\\037] * # \"normal\" atoms and or spaces (?: (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) | \" # \" [^\\\\\\x80-\\xff\\n\\015\"] * # normal (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015\"] * )* # ( special normal* )* \" # \" ) # \"special\" comment or quoted string [^()<>@,;:\".\\\\\\[\\]\\x80-\\xff\\000-\\010\\012-\\037] * # more \"normal\" )* < [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # < (?: @ [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional trailing comments (?: \\. [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional trailing comments )* (?: , [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. @ [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional trailing comments (?: \\. [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional trailing comments )* )* # additional domains : [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional trailing comments )? # optional route (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom # Atom | # or \" # \" [^\\\\\\x80-\\xff\\n\\015\"] * # normal (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015\"] * )* # ( special normal* )* \" # \" # Quoted string ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: \\. [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom # Atom | # or \" # \" [^\\\\\\x80-\\xff\\n\\015\"] * # normal (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015\"] * )* # ( special normal* )* \" # \" # Quoted string ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # additional words )* @ [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional trailing comments (?: \\. [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional trailing comments )* # address spec > # > # name and address ) " nil nil nil t "A missing angle @,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom # Atom | # or \" # \" [^\\\\\\x80-\\xff\\n\\015\"] * # normal (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015\"] * )* # ( special normal* )* \" # \" # Quoted string ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: \\. [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom # Atom | # or \" # \" [^\\\\\\x80-\\xff\\n\\015\"] * # normal (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015\"] * )* # ( special normal* )* \" # \" # Quoted string ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # additional words )* @ [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional trailing comments (?: \\. [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional trailing comments )* # address | # or (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom # Atom | # or \" # \" [^\\\\\\x80-\\xff\\n\\015\"] * # normal (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015\"] * )* # ( special normal* )* \" # \" # Quoted string ) # leading word [^()<>@,;:\".\\\\\\[\\]\\x80-\\xff\\000-\\010\\012-\\037] * # \"normal\" atoms and or spaces (?: (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) | \" # \" [^\\\\\\x80-\\xff\\n\\015\"] * # normal (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015\"] * )* # ( special normal* )* \" # \" ) # \"special\" comment or quoted string [^()<>@,;:\".\\\\\\[\\]\\x80-\\xff\\000-\\010\\012-\\037] * # more \"normal\" )* < [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # < (?: @ [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional trailing comments (?: \\. [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional trailing comments )* (?: , [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. @ [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional trailing comments (?: \\. [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional trailing comments )* )* # additional domains : [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional trailing comments )? # optional route (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom # Atom | # or \" # \" [^\\\\\\x80-\\xff\\n\\015\"] * # normal (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015\"] * )* # ( special normal* )* \" # \" # Quoted string ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: \\. [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom # Atom | # or \" # \" [^\\\\\\x80-\\xff\\n\\015\"] * # normal (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015\"] * )* # ( special normal* )* \" # \" # Quoted string ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # additional words )* @ [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional trailing comments (?: \\. [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional trailing comments )* # address spec > # > # name and address ) /x" "[\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional leading comment (?: (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom # Atom | # or \" # \" [^\\\\\\x80-\\xff\\n\\015\"] * # normal (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015\"] * )* # ( special normal* )* \" # \" # Quoted string ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: \\. [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom # Atom | # or \" # \" [^\\\\\\x80-\\xff\\n\\015\"] * # normal (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015\"] * )* # ( special normal* )* \" # \" # Quoted string ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # additional words )* @ [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional trailing comments (?: \\. [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional trailing comments )* # address | # or (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom # Atom | # or \" # \" [^\\\\\\x80-\\xff\\n\\015\"] * # normal (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015\"] * )* # ( special normal* )* \" # \" # Quoted string ) # leading word [^()<>@,;:\".\\\\\\[\\]\\x80-\\xff\\000-\\010\\012-\\037] * # \"normal\" atoms and or spaces (?: (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) | \" # \" [^\\\\\\x80-\\xff\\n\\015\"] * # normal (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015\"] * )* # ( special normal* )* \" # \" ) # \"special\" comment or quoted string [^()<>@,;:\".\\\\\\[\\]\\x80-\\xff\\000-\\010\\012-\\037] * # more \"normal\" )* < [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # < (?: @ [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional trailing comments (?: \\. [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional trailing comments )* (?: , [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. @ [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional trailing comments (?: \\. [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional trailing comments )* )* # additional domains : [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional trailing comments )? # optional route (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom # Atom | # or \" # \" [^\\\\\\x80-\\xff\\n\\015\"] * # normal (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015\"] * )* # ( special normal* )* \" # \" # Quoted string ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: \\. [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom # Atom | # or \" # \" [^\\\\\\x80-\\xff\\n\\015\"] * # normal (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015\"] * )* # ( special normal* )* \" # \" # Quoted string ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # additional words )* @ [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional trailing comments (?: \\. [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. (?: [^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]+ # some number of atom characters... (?![^(\\040)<>@,;:\".\\\\\\[\\]\\000-\\037\\x80-\\xff]) # ..not followed by something that could be part of an atom | \\[ # [ (?: [^\\\\\\x80-\\xff\\n\\015\\[\\]] | \\\\ [^\\x80-\\xff] )* # stuff \\] # ] ) [\\040\\t]* # Nab whitespace. (?: \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: # ( (?: \\\\ [^\\x80-\\xff] | \\( # ( [^\\\\\\x80-\\xff\\n\\015()] * # normal* (?: \\\\ [^\\x80-\\xff] [^\\\\\\x80-\\xff\\n\\015()] * )* # (special normal*)* \\) # ) ) # special [^\\\\\\x80-\\xff\\n\\015()] * # normal* )* # )* \\) # ) [\\040\\t]* )* # If comment found, allow more spaces. # optional trailing comments )* # address spec > # > # name and address ) " nil nil nil t "The quick brown fox" nil nil nil) (305 "\"abc\\0def\\00pqr\\000xyz\\0000AB\" =~ /abc\\0def\\00pqr\\000xyz\\0000AB/" "abc\\0def\\00pqr\\000xyz\\0000AB" nil nil nil nil ("abc" 0 "def" 0 "pqr" 0 "xyz" 0 "0AB") nil ("abc" 0 "def" 0 "pqr" 0 "xyz" 0 "0AB") (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (306 "\"abc456 abc\\0def\\00pqr\\000xyz\\0000ABCDE\" =~ /abc\\0def\\00pqr\\000xyz\\0000AB/" "abc\\0def\\00pqr\\000xyz\\0000AB" nil nil nil nil ("abc456 abc" 0 "def" 0 "pqr" 0 "xyz" 0 "0ABCDE") nil ("abc" 0 "def" 0 "pqr" 0 "xyz" 0 "0AB") (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (307 "\"abc\\x0def\\x00pqr\\x000xyz\\x0000AB\" =~ /abc\\x0def\\x00pqr\\x000xyz\\x0000AB/" "abc\\x0def\\x00pqr\\x000xyz\\x0000AB" nil nil nil nil ("abc" 13 "ef" 0 "pqr" 0 "0xyz" 0 "00AB") nil ("abc" 13 "ef" 0 "pqr" 0 "0xyz" 0 "00AB") (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (308 "\"abc456 abc\\x0def\\x00pqr\\x000xyz\\x0000ABCDE\" =~ /abc\\x0def\\x00pqr\\x000xyz\\x0000AB/" "abc\\x0def\\x00pqr\\x000xyz\\x0000AB" nil nil nil nil ("abc456 abc" 13 "ef" 0 "pqr" 0 "0xyz" 0 "00ABCDE") nil ("abc" 13 "ef" 0 "pqr" 0 "0xyz" 0 "00AB") (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (309 "\"\\0A\" =~ /^[\\000-\\037]/" "^[\\000-\\037]" nil nil nil nil ("" 0 "A") nil ("" 0) (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (310 "\"\\01B\" =~ /^[\\000-\\037]/" "^[\\000-\\037]" nil nil nil nil ("" 1 "B") nil ("" 1) (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (311 "\"\\037C\" =~ /^[\\000-\\037]/" "^[\\000-\\037]" nil nil nil nil ("" 31 "C") nil ("" 31) (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (312 "\"\\0\\0\\0\\0\" =~ /\\0*/" "\\0*" nil nil nil nil ("" 0 0 0 0) nil ("" 0 0 0 0) (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (313 "\"The A\\x0\\x0Z\" =~ /A\\x0{2,3}Z/" "A\\x0{2,3}Z" nil nil nil nil ("The A" 0 0 "Z") nil ("A" 0 0 "Z") (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (314 "\"An A\\0\\x0\\0Z\" =~ /A\\x0{2,3}Z/" "A\\x0{2,3}Z" nil nil nil nil ("An A" 0 0 0 "Z") nil ("A" 0 0 0 "Z") (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (315 "\"A\\0Z\" =~ /A\\x0{2,3}Z/" "A\\x0{2,3}Z" nil nil nil nil ("A" 0 "Z") nil nil nil) (316 "\"A\\0\\x0\\0\\x0Z\" =~ /A\\x0{2,3}Z/" "A\\x0{2,3}Z" nil nil nil nil ("A" 0 0 0 0 "Z") nil nil nil) (317 "\"cowcowbell\" =~ /^(cow|)\\1(bell)/" "^(cow|)\\1(bell)" nil nil nil nil "cowcowbell" nil "cowcowbell" ("cow" "bell" nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (318 "\"bell\" =~ /^(cow|)\\1(bell)/" "^(cow|)\\1(bell)" nil nil nil nil "bell" nil "bell" ("" "bell" nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (319 "\"cowbell\" =~ /^(cow|)\\1(bell)/" "^(cow|)\\1(bell)" nil nil nil nil "cowbell" nil nil nil) (320 "\"\\040abc\" =~ /^\\s/" "^\\s" nil nil nil nil " abc" nil " " (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (321 "\"\\x0cabc\" =~ /^\\s/" "^\\s" nil nil nil nil ("" 12 "abc") nil ("" 12) (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (322 "\"\\nabc\" =~ /^\\s/" "^\\s" nil nil nil nil " abc" nil " " (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (323 "\"\\rabc\" =~ /^\\s/" "^\\s" nil nil nil nil ("" 13 "abc") nil ("" 13) (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (324 "\"\\tabc\" =~ /^\\s/" "^\\s" nil nil nil nil ("" 9 "abc") nil ("" 9) (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (325 "\"abc\" =~ /^\\s/" "^\\s" nil nil nil nil "abc" nil nil nil) (326 ("\"abc\" =~ /^a" 9 "b" 10 " " 13 " " 12 " c/x") "^a b c" nil nil nil t "abc" nil "abc" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (327 "\"ab\" =~ /^(a|)\\1*b/" "^(a|)\\1*b" nil nil nil nil "ab" nil "ab" ("a" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (328 "\"aaaab\" =~ /^(a|)\\1*b/" "^(a|)\\1*b" nil nil nil nil "aaaab" nil "aaaab" ("a" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (329 "\"b\" =~ /^(a|)\\1*b/" "^(a|)\\1*b" nil nil nil nil "b" nil "b" ("" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (330 "\"acb\" =~ /^(a|)\\1*b/" "^(a|)\\1*b" nil nil nil nil "acb" nil nil nil) (331 "\"aab\" =~ /^(a|)\\1+b/" "^(a|)\\1+b" nil nil nil nil "aab" nil "aab" ("a" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (332 "\"aaaab\" =~ /^(a|)\\1+b/" "^(a|)\\1+b" nil nil nil nil "aaaab" nil "aaaab" ("a" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (333 "\"b\" =~ /^(a|)\\1+b/" "^(a|)\\1+b" nil nil nil nil "b" nil "b" ("" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (334 "\"ab\" =~ /^(a|)\\1+b/" "^(a|)\\1+b" nil nil nil nil "ab" nil nil nil) (335 "\"ab\" =~ /^(a|)\\1?b/" "^(a|)\\1?b" nil nil nil nil "ab" nil "ab" ("a" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (336 "\"aab\" =~ /^(a|)\\1?b/" "^(a|)\\1?b" nil nil nil nil "aab" nil "aab" ("a" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (337 "\"b\" =~ /^(a|)\\1?b/" "^(a|)\\1?b" nil nil nil nil "b" nil "b" ("" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (338 "\"acb\" =~ /^(a|)\\1?b/" "^(a|)\\1?b" nil nil nil nil "acb" nil nil nil) (339 "\"aaab\" =~ /^(a|)\\1{2}b/" "^(a|)\\1{2}b" nil nil nil nil "aaab" nil "aaab" ("a" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (340 "\"b\" =~ /^(a|)\\1{2}b/" "^(a|)\\1{2}b" nil nil nil nil "b" nil "b" ("" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (341 "\"ab\" =~ /^(a|)\\1{2}b/" "^(a|)\\1{2}b" nil nil nil nil "ab" nil nil nil) (342 "\"aab\" =~ /^(a|)\\1{2}b/" "^(a|)\\1{2}b" nil nil nil nil "aab" nil nil nil) (343 "\"aaaab\" =~ /^(a|)\\1{2}b/" "^(a|)\\1{2}b" nil nil nil nil "aaaab" nil nil nil) (344 "\"aaab\" =~ /^(a|)\\1{2,3}b/" "^(a|)\\1{2,3}b" nil nil nil nil "aaab" nil "aaab" ("a" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (345 "\"aaaab\" =~ /^(a|)\\1{2,3}b/" "^(a|)\\1{2,3}b" nil nil nil nil "aaaab" nil "aaaab" ("a" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (346 "\"b\" =~ /^(a|)\\1{2,3}b/" "^(a|)\\1{2,3}b" nil nil nil nil "b" nil "b" ("" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (347 "\"ab\" =~ /^(a|)\\1{2,3}b/" "^(a|)\\1{2,3}b" nil nil nil nil "ab" nil nil nil) (348 "\"aab\" =~ /^(a|)\\1{2,3}b/" "^(a|)\\1{2,3}b" nil nil nil nil "aab" nil nil nil) (349 "\"aaaaab\" =~ /^(a|)\\1{2,3}b/" "^(a|)\\1{2,3}b" nil nil nil nil "aaaaab" nil nil nil) (350 "\"abbbbc\" =~ /ab{1,3}bc/" "ab{1,3}bc" nil nil nil nil "abbbbc" nil "abbbbc" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (351 "\"abbbc\" =~ /ab{1,3}bc/" "ab{1,3}bc" nil nil nil nil "abbbc" nil "abbbc" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (352 "\"abbc\" =~ /ab{1,3}bc/" "ab{1,3}bc" nil nil nil nil "abbc" nil "abbc" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (353 "\"abc\" =~ /ab{1,3}bc/" "ab{1,3}bc" nil nil nil nil "abc" nil nil nil) (354 "\"abbbbbc\" =~ /ab{1,3}bc/" "ab{1,3}bc" nil nil nil nil "abbbbbc" nil nil nil) (355 "\"track1.title:TBlah blah blah\" =~ /([^.]*)\\.([^:]*):[T ]+(.*)/" "([^.]*)\\.([^:]*):[T ]+(.*)" nil nil nil nil "track1.title:TBlah blah blah" nil "track1.title:TBlah blah blah" ("track1" "title" "Blah blah blah" nil nil nil nil nil nil nil nil nil nil nil nil nil)) (356 "\"track1.title:TBlah blah blah\" =~ /([^.]*)\\.([^:]*):[T ]+(.*)/i" "([^.]*)\\.([^:]*):[T ]+(.*)" t nil nil nil "track1.title:TBlah blah blah" nil "track1.title:TBlah blah blah" ("track1" "title" "Blah blah blah" nil nil nil nil nil nil nil nil nil nil nil nil nil)) (357 "\"track1.title:TBlah blah blah\" =~ /([^.]*)\\.([^:]*):[t ]+(.*)/i" "([^.]*)\\.([^:]*):[t ]+(.*)" t nil nil nil "track1.title:TBlah blah blah" nil "track1.title:TBlah blah blah" ("track1" "title" "Blah blah blah" nil nil nil nil nil nil nil nil nil nil nil nil nil)) (358 "\"WXY_^abc\" =~ /^[W-c]+$/" "^[W-c]+$" nil nil nil nil "WXY_^abc" nil "WXY_^abc" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (359 "\"wxy\" =~ /^[W-c]+$/" "^[W-c]+$" nil nil nil nil "wxy" nil nil nil) (360 "\"WXY_^abc\" =~ /^[W-c]+$/i" "^[W-c]+$" t nil nil nil "WXY_^abc" nil "WXY_^abc" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (361 "\"wxy_^ABC\" =~ /^[W-c]+$/i" "^[W-c]+$" t nil nil nil "wxy_^ABC" nil "wxy_^ABC" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (362 "\"WXY_^abc\" =~ /^[\\x3f-\\x5F]+$/i" "^[\\x3f-\\x5F]+$" t nil nil nil "WXY_^abc" nil "WXY_^abc" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (363 "\"wxy_^ABC\" =~ /^[\\x3f-\\x5F]+$/i" "^[\\x3f-\\x5F]+$" t nil nil nil "wxy_^ABC" nil "wxy_^ABC" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (364 "\"abc\" =~ /^abc$/m" "^abc$" nil t nil nil "abc" nil "abc" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (365 "\"qqq\\nabc\" =~ /^abc$/m" "^abc$" nil t nil nil "qqq abc" nil "abc" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (366 "\"abc\\nzzz\" =~ /^abc$/m" "^abc$" nil t nil nil "abc zzz" nil "abc" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (367 "\"qqq\\nabc\\nzzz\" =~ /^abc$/m" "^abc$" nil t nil nil "qqq abc zzz" nil "abc" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (368 "\"abc\" =~ /^abc$/" "^abc$" nil nil nil nil "abc" nil "abc" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (369 "\"qqq\\nabc\" =~ /^abc$/" "^abc$" nil nil nil nil "qqq abc" nil nil nil) (370 "\"abc\\nzzz\" =~ /^abc$/" "^abc$" nil nil nil nil "abc zzz" nil nil nil) (371 "\"qqq\\nabc\\nzzz\" =~ /^abc$/" "^abc$" nil nil nil nil "qqq abc zzz" nil nil nil) (372 "\"abc\" =~ /\\Aabc\\Z/m" "\\Aabc\\Z" nil t nil nil "abc" nil "abc" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (373 "\"abc\\n\" =~ /\\Aabc\\Z/m" "\\Aabc\\Z" nil t nil nil "abc " nil "abc" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (374 "\"qqq\\nabc\" =~ /\\Aabc\\Z/m" "\\Aabc\\Z" nil t nil nil "qqq abc" nil nil nil) (375 "\"abc\\nzzz\" =~ /\\Aabc\\Z/m" "\\Aabc\\Z" nil t nil nil "abc zzz" nil nil nil) (376 "\"qqq\\nabc\\nzzz\" =~ /\\Aabc\\Z/m" "\\Aabc\\Z" nil t nil nil "qqq abc zzz" nil nil nil) (377 "\"abc\\ndef\" =~ /\\A(.)*\\Z/s" "\\A(.)*\\Z" nil nil t nil "abc def" nil "abc def" ("f" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (378 "\"abc\\ndef\" =~ /\\A(.)*\\Z/m" "\\A(.)*\\Z" nil t nil nil "abc def" nil nil nil) (379 "\"b::c\" =~ /(?:b)|(?::+)/" "(?:b)|(?::+)" nil nil nil nil "b::c" nil "b" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (380 "\"c::b\" =~ /(?:b)|(?::+)/" "(?:b)|(?::+)" nil nil nil nil "c::b" nil "::" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (381 "\"az-\" =~ /[-az]+/" "[-az]+" nil nil nil nil "az-" nil "az-" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (382 "\"b\" =~ /[-az]+/" "[-az]+" nil nil nil nil "b" nil nil nil) (383 "\"za-\" =~ /[az-]+/" "[az-]+" nil nil nil nil "za-" nil "za-" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (384 "\"b\" =~ /[az-]+/" "[az-]+" nil nil nil nil "b" nil nil nil) (385 "\"a-z\" =~ /[a\\-z]+/" "[a\\-z]+" nil nil nil nil "a-z" nil "a-z" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (386 "\"b\" =~ /[a\\-z]+/" "[a\\-z]+" nil nil nil nil "b" nil nil nil) (387 "\"abcdxyz\" =~ /[a-z]+/" "[a-z]+" nil nil nil nil "abcdxyz" nil "abcdxyz" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (388 "\"12-34\" =~ /[\\d-]+/" "[\\d-]+" nil nil nil nil "12-34" nil "12-34" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (389 "\"aaa\" =~ /[\\d-]+/" "[\\d-]+" nil nil nil nil "aaa" nil nil nil) (390 "\"12-34z\" =~ /[\\d-z]+/" "[\\d-z]+" nil nil nil nil "12-34z" nil "12-34z" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (391 "\"aaa\" =~ /[\\d-z]+/" "[\\d-z]+" nil nil nil nil "aaa" nil nil nil) (392 "\"\\\\\" =~ /\\x5c/" "\\x5c" nil nil nil nil "\\" nil "\\" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (393 "\"the Zoo\" =~ /\\x20Z/" "\\x20Z" nil nil nil nil "the Zoo" nil " Z" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (394 "\"Zulu\" =~ /\\x20Z/" "\\x20Z" nil nil nil nil "Zulu" nil nil nil) (395 "\"abcabc\" =~ /(abc)\\1/i" "(abc)\\1" t nil nil nil "abcabc" nil "abcabc" ("abc" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (396 "\"ABCabc\" =~ /(abc)\\1/i" "(abc)\\1" t nil nil nil "ABCabc" nil "ABCabc" ("ABC" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (397 "\"abcABC\" =~ /(abc)\\1/i" "(abc)\\1" t nil nil nil "abcABC" nil "abcABC" ("abc" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (398 "\"ab{3cd\" =~ /ab{3cd/" "ab{3cd" nil nil nil nil "ab{3cd" nil "ab{3cd" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (399 "\"ab{3,cd\" =~ /ab{3,cd/" "ab{3,cd" nil nil nil nil "ab{3,cd" nil "ab{3,cd" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (400 "\"ab{3,4a}cd\" =~ /ab{3,4a}cd/" "ab{3,4a}cd" nil nil nil nil "ab{3,4a}cd" nil "ab{3,4a}cd" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (401 "\"{4,5a}bc\" =~ /{4,5a}bc/" "{4,5a}bc" nil nil nil nil "{4,5a}bc" nil "{4,5a}bc" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (402 "\"a\\rb\" =~ /^a.b/" "^a.b" nil nil nil nil ("a" 13 "b") nil ("a" 13 "b") (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (403 "\"a\\nb\" =~ /^a.b/" "^a.b" nil nil nil nil "a b" nil nil nil) (404 "\"abc\" =~ /abc$/" "abc$" nil nil nil nil "abc" nil "abc" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (405 "\"abc\\n\" =~ /abc$/" "abc$" nil nil nil nil "abc " nil "abc" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (406 "\"abc\\ndef\" =~ /abc$/" "abc$" nil nil nil nil "abc def" nil nil nil) (407 "\"abc\\x53\" =~ /(abc)\\123/" "(abc)\\123" nil nil nil nil "abcS" nil "abcS" ("abc" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (408 "\"abc\\x93\" =~ /(abc)\\223/" "(abc)\\223" nil nil nil nil ("abc" 147) nil ("abc" 147) ("abc" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (409 "\"abc\\xd3\" =~ /(abc)\\323/" "(abc)\\323" nil nil nil nil ("abc" 211) nil ("abc" 211) ("abc" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (410 "\"abc\\x40\" =~ /(abc)\\500/" "(abc)\\500" nil nil nil nil "abc@" nil "abc@" ("abc" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (411 "\"abc\\100\" =~ /(abc)\\500/" "(abc)\\500" nil nil nil nil "abc@" nil "abc@" ("abc" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (412 "\"abc\\x400\" =~ /(abc)\\5000/" "(abc)\\5000" nil nil nil nil "abc@0" nil "abc@0" ("abc" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (413 "\"abc\\x40\\x30\" =~ /(abc)\\5000/" "(abc)\\5000" nil nil nil nil "abc@0" nil "abc@0" ("abc" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (414 "\"abc\\1000\" =~ /(abc)\\5000/" "(abc)\\5000" nil nil nil nil "abc@0" nil "abc@0" ("abc" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (415 "\"abc\\100\\x30\" =~ /(abc)\\5000/" "(abc)\\5000" nil nil nil nil "abc@0" nil "abc@0" ("abc" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (416 "\"abc\\100\\060\" =~ /(abc)\\5000/" "(abc)\\5000" nil nil nil nil "abc@0" nil "abc@0" ("abc" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (417 "\"abc\\100\\60\" =~ /(abc)\\5000/" "(abc)\\5000" nil nil nil nil "abc@0" nil "abc@0" ("abc" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (418 "\"abc\\081\" =~ /abc\\81/" "abc\\81" nil nil nil nil ("abc" 0 "81") nil ("abc" 0 "81") (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (419 "\"abc\\0\\x38\\x31\" =~ /abc\\81/" "abc\\81" nil nil nil nil ("abc" 0 "81") nil ("abc" 0 "81") (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (420 "\"abc\\091\" =~ /abc\\91/" "abc\\91" nil nil nil nil ("abc" 0 "91") nil ("abc" 0 "91") (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (421 "\"abc\\0\\x39\\x31\" =~ /abc\\91/" "abc\\91" nil nil nil nil ("abc" 0 "91") nil ("abc" 0 "91") (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (422 "\"abcdefghijkllS\" =~ /(a)(b)(c)(d)(e)(f)(g)(h)(i)(j)(k)(l)\\12\\123/" "(a)(b)(c)(d)(e)(f)(g)(h)(i)(j)(k)(l)\\12\\123" nil nil nil nil "abcdefghijkllS" nil "abcdefghijkllS" ("a" "b" "c" "d" "e" "f" "g" "h" "i" "j" "k" "l" nil nil nil nil)) (423 "\"abcdefghijk\\12S\" =~ /(a)(b)(c)(d)(e)(f)(g)(h)(i)(j)(k)\\12\\123/" "(a)(b)(c)(d)(e)(f)(g)(h)(i)(j)(k)\\12\\123" nil nil nil nil "abcdefghijk S" nil "abcdefghijk S" ("a" "b" "c" "d" "e" "f" "g" "h" "i" "j" "k" nil nil nil nil nil)) (424 "\"abgdef\" =~ /ab\\gdef/" "ab\\gdef" nil nil nil nil "abgdef" nil "abgdef" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (425 "\"bc\" =~ /a{0}bc/" "a{0}bc" nil nil nil nil "bc" nil "bc" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (426 "\"xyz\" =~ /(a|(bc)){0,0}?xyz/" "(a|(bc)){0,0}?xyz" nil nil nil nil "xyz" nil "xyz" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (427 "\"abc\\010de\" =~ /abc[\\10]de/" "abc[\\10]de" nil nil nil nil ("abc" 8 "de") nil ("abc" 8 "de") (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (428 "\"abc\\1de\" =~ /abc[\\1]de/" "abc[\\1]de" nil nil nil nil ("abc" 1 "de") nil ("abc" 1 "de") (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (429 "\"abc\\1de\" =~ /(abc)[\\1]de/" "(abc)[\\1]de" nil nil nil nil ("abc" 1 "de") nil ("abc" 1 "de") ("abc" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (430 "\"a\\nb\" =~ /a.b(?s)/" "a.b(?s)" nil nil nil nil "a b" nil nil nil) (431 "\"baNOTccccd\" =~ /^([^a])([^\\b])([^c]*)([^d]{3,4})/" "^([^a])([^\\b])([^c]*)([^d]{3,4})" nil nil nil nil "baNOTccccd" nil "baNOTcccc" ("b" "a" "NOT" "cccc" nil nil nil nil nil nil nil nil nil nil nil nil)) (432 "\"baNOTcccd\" =~ /^([^a])([^\\b])([^c]*)([^d]{3,4})/" "^([^a])([^\\b])([^c]*)([^d]{3,4})" nil nil nil nil "baNOTcccd" nil "baNOTccc" ("b" "a" "NOT" "ccc" nil nil nil nil nil nil nil nil nil nil nil nil)) (433 "\"baNOTccd\" =~ /^([^a])([^\\b])([^c]*)([^d]{3,4})/" "^([^a])([^\\b])([^c]*)([^d]{3,4})" nil nil nil nil "baNOTccd" nil "baNOTcc" ("b" "a" "NO" "Tcc" nil nil nil nil nil nil nil nil nil nil nil nil)) (434 "\"bacccd\" =~ /^([^a])([^\\b])([^c]*)([^d]{3,4})/" "^([^a])([^\\b])([^c]*)([^d]{3,4})" nil nil nil nil "bacccd" nil "baccc" ("b" "a" "" "ccc" nil nil nil nil nil nil nil nil nil nil nil nil)) (435 "\"anything\" =~ /^([^a])([^\\b])([^c]*)([^d]{3,4})/" "^([^a])([^\\b])([^c]*)([^d]{3,4})" nil nil nil nil "anything" nil nil nil) (436 "\"b\\bc\" =~ /^([^a])([^\\b])([^c]*)([^d]{3,4})/" "^([^a])([^\\b])([^c]*)([^d]{3,4})" nil nil nil nil ("b" 8 "c") nil nil nil) (437 "\"baccd\" =~ /^([^a])([^\\b])([^c]*)([^d]{3,4})/" "^([^a])([^\\b])([^c]*)([^d]{3,4})" nil nil nil nil "baccd" nil nil nil) (438 "\"Abc\" =~ /[^a]/" "[^a]" nil nil nil nil "Abc" nil "A" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (439 "\"Abc\" =~ /[^a]/i" "[^a]" t nil nil nil "Abc" nil "b" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (440 "\"AAAaAbc\" =~ /[^a]+/" "[^a]+" nil nil nil nil "AAAaAbc" nil "AAA" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (441 "\"AAAaAbc\" =~ /[^a]+/i" "[^a]+" t nil nil nil "AAAaAbc" nil "bc" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (442 "\"bbb\\nccc\" =~ /[^a]+/" "[^a]+" nil nil nil nil "bbb ccc" nil "bbb ccc" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (443 "\"abc\" =~ /[^k]$/" "[^k]$" nil nil nil nil "abc" nil "c" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (444 "\"abk\" =~ /[^k]$/" "[^k]$" nil nil nil nil "abk" nil nil nil) (445 "\"abc\" =~ /[^k]{2,3}$/" "[^k]{2,3}$" nil nil nil nil "abc" nil "abc" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (446 "\"kbc\" =~ /[^k]{2,3}$/" "[^k]{2,3}$" nil nil nil nil "kbc" nil "bc" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (447 "\"kabc\" =~ /[^k]{2,3}$/" "[^k]{2,3}$" nil nil nil nil "kabc" nil "abc" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (448 "\"abk\" =~ /[^k]{2,3}$/" "[^k]{2,3}$" nil nil nil nil "abk" nil nil nil) (449 "\"akb\" =~ /[^k]{2,3}$/" "[^k]{2,3}$" nil nil nil nil "akb" nil nil nil) (450 "\"akk\" =~ /[^k]{2,3}$/" "[^k]{2,3}$" nil nil nil nil "akk" nil nil nil) (451 "\"12345678\\@a.b.c.d\" =~ /^\\d{8,}\\@.+[^k]$/" "^\\d{8,}\\@.+[^k]$" nil nil nil nil "12345678@a.b.c.d" nil "12345678@a.b.c.d" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (452 "\"123456789\\@x.y.z\" =~ /^\\d{8,}\\@.+[^k]$/" "^\\d{8,}\\@.+[^k]$" nil nil nil nil "123456789@x.y.z" nil "123456789@x.y.z" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (453 "\"12345678\\@x.y.uk\" =~ /^\\d{8,}\\@.+[^k]$/" "^\\d{8,}\\@.+[^k]$" nil nil nil nil "12345678@x.y.uk" nil nil nil) (454 "\"1234567\\@a.b.c.d\" =~ /^\\d{8,}\\@.+[^k]$/" "^\\d{8,}\\@.+[^k]$" nil nil nil nil "1234567@a.b.c.d" nil nil nil) (455 "\"aaaaaaaaa\" =~ /(a)\\1{8,}/" "(a)\\1{8,}" nil nil nil nil "aaaaaaaaa" nil "aaaaaaaaa" ("a" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (456 "\"aaaaaaaaaa\" =~ /(a)\\1{8,}/" "(a)\\1{8,}" nil nil nil nil "aaaaaaaaaa" nil "aaaaaaaaaa" ("a" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (457 "\"aaaaaaa\" =~ /(a)\\1{8,}/" "(a)\\1{8,}" nil nil nil nil "aaaaaaa" nil nil nil) (458 "\"aaaabcd\" =~ /[^a]/" "[^a]" nil nil nil nil "aaaabcd" nil "b" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (459 "\"aaAabcd\" =~ /[^a]/" "[^a]" nil nil nil nil "aaAabcd" nil "A" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (460 "\"aaaabcd\" =~ /[^a]/i" "[^a]" t nil nil nil "aaaabcd" nil "b" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (461 "\"aaAabcd\" =~ /[^a]/i" "[^a]" t nil nil nil "aaAabcd" nil "b" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (462 "\"aaaabcd\" =~ /[^az]/" "[^az]" nil nil nil nil "aaaabcd" nil "b" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (463 "\"aaAabcd\" =~ /[^az]/" "[^az]" nil nil nil nil "aaAabcd" nil "A" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (464 "\"aaaabcd\" =~ /[^az]/i" "[^az]" t nil nil nil "aaaabcd" nil "b" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (465 "\"aaAabcd\" =~ /[^az]/i" "[^az]" t nil nil nil "aaAabcd" nil "b" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (466 "\"\\000\\001\\002\\003\\004\\005\\006\\007\\010\\011\\012\\013\\014\\015\\016\\017\\020\\021\\022\\023\\024\\025\\026\\027\\030\\031\\032\\033\\034\\035\\036\\037\\040\\041\\042\\043\\044\\045\\046\\047\\050\\051\\052\\053\\054\\055\\056\\057\\060\\061\\062\\063\\064\\065\\066\\067\\070\\071\\072\\073\\074\\075\\076\\077\\100\\101\\102\\103\\104\\105\\106\\107\\110\\111\\112\\113\\114\\115\\116\\117\\120\\121\\122\\123\\124\\125\\126\\127\\130\\131\\132\\133\\134\\135\\136\\137\\140\\141\\142\\143\\144\\145\\146\\147\\150\\151\\152\\153\\154\\155\\156\\157\\160\\161\\162\\163\\164\\165\\166\\167\\170\\171\\172\\173\\174\\175\\176\\177\\200\\201\\202\\203\\204\\205\\206\\207\\210\\211\\212\\213\\214\\215\\216\\217\\220\\221\\222\\223\\224\\225\\226\\227\\230\\231\\232\\233\\234\\235\\236\\237\\240\\241\\242\\243\\244\\245\\246\\247\\250\\251\\252\\253\\254\\255\\256\\257\\260\\261\\262\\263\\264\\265\\266\\267\\270\\271\\272\\273\\274\\275\\276\\277\\300\\301\\302\\303\\304\\305\\306\\307\\310\\311\\312\\313\\314\\315\\316\\317\\320\\321\\322\\323\\324\\325\\326\\327\\330\\331\\332\\333\\334\\335\\336\\337\\340\\341\\342\\343\\344\\345\\346\\347\\350\\351\\352\\353\\354\\355\\356\\357\\360\\361\\362\\363\\364\\365\\366\\367\\370\\371\\372\\373\\374\\375\\376\\377\" =~ /\\000\\001\\002\\003\\004\\005\\006\\007\\010\\011\\012\\013\\014\\015\\016\\017\\020\\021\\022\\023\\024\\025\\026\\027\\030\\031\\032\\033\\034\\035\\036\\037\\040\\041\\042\\043\\044\\045\\046\\047\\050\\051\\052\\053\\054\\055\\056\\057\\060\\061\\062\\063\\064\\065\\066\\067\\070\\071\\072\\073\\074\\075\\076\\077\\100\\101\\102\\103\\104\\105\\106\\107\\110\\111\\112\\113\\114\\115\\116\\117\\120\\121\\122\\123\\124\\125\\126\\127\\130\\131\\132\\133\\134\\135\\136\\137\\140\\141\\142\\143\\144\\145\\146\\147\\150\\151\\152\\153\\154\\155\\156\\157\\160\\161\\162\\163\\164\\165\\166\\167\\170\\171\\172\\173\\174\\175\\176\\177\\200\\201\\202\\203\\204\\205\\206\\207\\210\\211\\212\\213\\214\\215\\216\\217\\220\\221\\222\\223\\224\\225\\226\\227\\230\\231\\232\\233\\234\\235\\236\\237\\240\\241\\242\\243\\244\\245\\246\\247\\250\\251\\252\\253\\254\\255\\256\\257\\260\\261\\262\\263\\264\\265\\266\\267\\270\\271\\272\\273\\274\\275\\276\\277\\300\\301\\302\\303\\304\\305\\306\\307\\310\\311\\312\\313\\314\\315\\316\\317\\320\\321\\322\\323\\324\\325\\326\\327\\330\\331\\332\\333\\334\\335\\336\\337\\340\\341\\342\\343\\344\\345\\346\\347\\350\\351\\352\\353\\354\\355\\356\\357\\360\\361\\362\\363\\364\\365\\366\\367\\370\\371\\372\\373\\374\\375\\376\\377/" "\\000\\001\\002\\003\\004\\005\\006\\007\\010\\011\\012\\013\\014\\015\\016\\017\\020\\021\\022\\023\\024\\025\\026\\027\\030\\031\\032\\033\\034\\035\\036\\037\\040\\041\\042\\043\\044\\045\\046\\047\\050\\051\\052\\053\\054\\055\\056\\057\\060\\061\\062\\063\\064\\065\\066\\067\\070\\071\\072\\073\\074\\075\\076\\077\\100\\101\\102\\103\\104\\105\\106\\107\\110\\111\\112\\113\\114\\115\\116\\117\\120\\121\\122\\123\\124\\125\\126\\127\\130\\131\\132\\133\\134\\135\\136\\137\\140\\141\\142\\143\\144\\145\\146\\147\\150\\151\\152\\153\\154\\155\\156\\157\\160\\161\\162\\163\\164\\165\\166\\167\\170\\171\\172\\173\\174\\175\\176\\177\\200\\201\\202\\203\\204\\205\\206\\207\\210\\211\\212\\213\\214\\215\\216\\217\\220\\221\\222\\223\\224\\225\\226\\227\\230\\231\\232\\233\\234\\235\\236\\237\\240\\241\\242\\243\\244\\245\\246\\247\\250\\251\\252\\253\\254\\255\\256\\257\\260\\261\\262\\263\\264\\265\\266\\267\\270\\271\\272\\273\\274\\275\\276\\277\\300\\301\\302\\303\\304\\305\\306\\307\\310\\311\\312\\313\\314\\315\\316\\317\\320\\321\\322\\323\\324\\325\\326\\327\\330\\331\\332\\333\\334\\335\\336\\337\\340\\341\\342\\343\\344\\345\\346\\347\\350\\351\\352\\353\\354\\355\\356\\357\\360\\361\\362\\363\\364\\365\\366\\367\\370\\371\\372\\373\\374\\375\\376\\377" nil nil nil nil ("" 0 1 2 3 4 5 6 7 8 9 10 11 12 13 14 15 16 17 18 19 20 21 22 23 24 25 26 27 28 29 30 31 " !\"#$%&'()*+,-./0123456789:;<=>?@ABCDEFGHIJKLMNOPQRSTUVWXYZ[\\]^_`abcdefghijklmnopqrstuvwxyz{|}~" 127 128 129 130 131 132 133 134 135 136 137 138 139 140 141 142 143 144 145 146 147 148 149 150 151 152 153 154 155 156 157 158 159 160 161 162 163 164 165 166 167 168 169 170 171 172 173 174 175 176 177 178 179 180 181 182 183 184 185 186 187 188 189 190 191 192 193 194 195 196 197 198 199 200 201 202 203 204 205 206 207 208 209 210 211 212 213 214 215 216 217 218 219 220 221 222 223 224 225 226 227 228 229 230 231 232 233 234 235 236 237 238 239 240 241 242 243 244 245 246 247 248 249 250 251 252 253 254 255) nil ("" 0 1 2 3 4 5 6 7 8 9 10 11 12 13 14 15 16 17 18 19 20 21 22 23 24 25 26 27 28 29 30 31 " !\"#$%&'()*+,-./0123456789:;<=>?@ABCDEFGHIJKLMNOPQRSTUVWXYZ[\\]^_`abcdefghijklmnopqrstuvwxyz{|}~" 127 128 129 130 131 132 133 134 135 136 137 138 139 140 141 142 143 144 145 146 147 148 149 150 151 152 153 154 155 156 157 158 159 160 161 162 163 164 165 166 167 168 169 170 171 172 173 174 175 176 177 178 179 180 181 182 183 184 185 186 187 188 189 190 191 192 193 194 195 196 197 198 199 200 201 202 203 204 205 206 207 208 209 210 211 212 213 214 215 216 217 218 219 220 221 222 223 224 225 226 227 228 229 230 231 232 233 234 235 236 237 238 239 240 241 242 243 244 245 246 247 248 249 250 251 252 253 254 255) (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (467 "\"xxxxxxxxxxxPSTAIREISLLxxxxxxxxx\" =~ /P[^*]TAIRE[^*]{1,6}?LL/" "P[^*]TAIRE[^*]{1,6}?LL" nil nil nil nil "xxxxxxxxxxxPSTAIREISLLxxxxxxxxx" nil "PSTAIREISLL" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (468 "\"xxxxxxxxxxxPSTAIREISLLxxxxxxxxx\" =~ /P[^*]TAIRE[^*]{1,}?LL/" "P[^*]TAIRE[^*]{1,}?LL" nil nil nil nil "xxxxxxxxxxxPSTAIREISLLxxxxxxxxx" nil "PSTAIREISLL" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (469 "\"1.230003938\" =~ /(\\.\\d\\d[1-9]?)\\d+/" "(\\.\\d\\d[1-9]?)\\d+" nil nil nil nil "1.230003938" nil ".230003938" (".23" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (470 "\"1.875000282\" =~ /(\\.\\d\\d[1-9]?)\\d+/" "(\\.\\d\\d[1-9]?)\\d+" nil nil nil nil "1.875000282" nil ".875000282" (".875" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (471 "\"1.235\" =~ /(\\.\\d\\d[1-9]?)\\d+/" "(\\.\\d\\d[1-9]?)\\d+" nil nil nil nil "1.235" nil ".235" (".23" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (472 "\"1.230003938\" =~ /(\\.\\d\\d((?=0)|\\d(?=\\d)))/" "(\\.\\d\\d((?=0)|\\d(?=\\d)))" nil nil nil nil "1.230003938" nil ".23" (".23" "" nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (473 "\"1.875000282\" =~ /(\\.\\d\\d((?=0)|\\d(?=\\d)))/" "(\\.\\d\\d((?=0)|\\d(?=\\d)))" nil nil nil nil "1.875000282" nil ".875" (".875" "5" nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (474 "\"1.235\" =~ /(\\.\\d\\d((?=0)|\\d(?=\\d)))/" "(\\.\\d\\d((?=0)|\\d(?=\\d)))" nil nil nil nil "1.235" nil nil nil) (475 "\"ab\" =~ /a(?)b/" "a(?)b" nil nil nil nil "ab" nil "ab" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (476 "\"Food is on the foo table\" =~ /\\b(foo)\\s+(\\w+)/i" "\\b(foo)\\s+(\\w+)" t nil nil nil "Food is on the foo table" nil "foo table" ("foo" "table" nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (477 "\"The food is under the bar in the barn.\" =~ /foo(.*)bar/" "foo(.*)bar" nil nil nil nil "The food is under the bar in the barn." nil "food is under the bar in the bar" ("d is under the bar in the " nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (478 "\"The food is under the bar in the barn.\" =~ /foo(.*?)bar/" "foo(.*?)bar" nil nil nil nil "The food is under the bar in the barn." nil "food is under the bar" ("d is under the " nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (479 "\"I have 2 numbers: 53147\" =~ /(.*)(\\d*)/" "(.*)(\\d*)" nil nil nil nil "I have 2 numbers: 53147" nil "I have 2 numbers: 53147" ("I have 2 numbers: 53147" "" nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (480 "\"I have 2 numbers: 53147\" =~ /(.*)(\\d+)/" "(.*)(\\d+)" nil nil nil nil "I have 2 numbers: 53147" nil "I have 2 numbers: 53147" ("I have 2 numbers: 5314" "7" nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (481 "\"I have 2 numbers: 53147\" =~ /(.*?)(\\d*)/" "(.*?)(\\d*)" nil nil nil nil "I have 2 numbers: 53147" nil "" ("" "" nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (482 "\"I have 2 numbers: 53147\" =~ /(.*?)(\\d+)/" "(.*?)(\\d+)" nil nil nil nil "I have 2 numbers: 53147" nil "I have 2" ("I have " "2" nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (483 "\"I have 2 numbers: 53147\" =~ /(.*)(\\d+)$/" "(.*)(\\d+)$" nil nil nil nil "I have 2 numbers: 53147" nil "I have 2 numbers: 53147" ("I have 2 numbers: 5314" "7" nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (484 "\"I have 2 numbers: 53147\" =~ /(.*?)(\\d+)$/" "(.*?)(\\d+)$" nil nil nil nil "I have 2 numbers: 53147" nil "I have 2 numbers: 53147" ("I have 2 numbers: " "53147" nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (485 "\"I have 2 numbers: 53147\" =~ /(.*)\\b(\\d+)$/" "(.*)\\b(\\d+)$" nil nil nil nil "I have 2 numbers: 53147" nil "I have 2 numbers: 53147" ("I have 2 numbers: " "53147" nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (486 "\"I have 2 numbers: 53147\" =~ /(.*\\D)(\\d+)$/" "(.*\\D)(\\d+)$" nil nil nil nil "I have 2 numbers: 53147" nil "I have 2 numbers: 53147" ("I have 2 numbers: " "53147" nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (487 "\"ABC123\" =~ /^\\D*(?!123)/" "^\\D*(?!123)" nil nil nil nil "ABC123" nil "AB" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (488 "\"ABC445\" =~ /^(\\D*)(?=\\d)(?!123)/" "^(\\D*)(?=\\d)(?!123)" nil nil nil nil "ABC445" nil "ABC" ("ABC" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (489 "\"ABC123\" =~ /^(\\D*)(?=\\d)(?!123)/" "^(\\D*)(?=\\d)(?!123)" nil nil nil nil "ABC123" nil nil nil) (490 "\"W46]789\" =~ /^[W-]46]/" "^[W-]46]" nil nil nil nil "W46]789" nil "W46]" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (491 "\"-46]789\" =~ /^[W-]46]/" "^[W-]46]" nil nil nil nil "-46]789" nil "-46]" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (492 "\"Wall\" =~ /^[W-]46]/" "^[W-]46]" nil nil nil nil "Wall" nil nil nil) (493 "\"Zebra\" =~ /^[W-]46]/" "^[W-]46]" nil nil nil nil "Zebra" nil nil nil) (494 "\"42\" =~ /^[W-]46]/" "^[W-]46]" nil nil nil nil "42" nil nil nil) (495 "\"[abcd]\" =~ /^[W-]46]/" "^[W-]46]" nil nil nil nil "[abcd]" nil nil nil) (496 "\"]abcd[\" =~ /^[W-]46]/" "^[W-]46]" nil nil nil nil "]abcd[" nil nil nil) (497 "\"W46]789\" =~ /^[W-\\]46]/" "^[W-\\]46]" nil nil nil nil "W46]789" nil "W" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (498 "\"Wall\" =~ /^[W-\\]46]/" "^[W-\\]46]" nil nil nil nil "Wall" nil "W" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (499 "\"Zebra\" =~ /^[W-\\]46]/" "^[W-\\]46]" nil nil nil nil "Zebra" nil "Z" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (500 "\"Xylophone\" =~ /^[W-\\]46]/" "^[W-\\]46]" nil nil nil nil "Xylophone" nil "X" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (501 "\"42\" =~ /^[W-\\]46]/" "^[W-\\]46]" nil nil nil nil "42" nil "4" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (502 "\"[abcd]\" =~ /^[W-\\]46]/" "^[W-\\]46]" nil nil nil nil "[abcd]" nil "[" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (503 "\"]abcd[\" =~ /^[W-\\]46]/" "^[W-\\]46]" nil nil nil nil "]abcd[" nil "]" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (504 "\"\\\\backslash\" =~ /^[W-\\]46]/" "^[W-\\]46]" nil nil nil nil "\\backslash" nil "\\" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (505 "\"-46]789\" =~ /^[W-\\]46]/" "^[W-\\]46]" nil nil nil nil "-46]789" nil nil nil) (506 "\"well\" =~ /^[W-\\]46]/" "^[W-\\]46]" nil nil nil nil "well" nil nil nil) (507 "\"01/01/2000\" =~ /\\d\\d\\/\\d\\d\\/\\d\\d\\d\\d/" "\\d\\d\\/\\d\\d\\/\\d\\d\\d\\d" nil nil nil nil "01/01/2000" nil "01/01/2000" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (508 "\"word cat dog elephant mussel cow horse canary baboon snake shark otherword\" =~ /word (?:[a-zA-Z0-9]+ ){0,10}otherword/" "word (?:[a-zA-Z0-9]+ ){0,10}otherword" nil nil nil nil "word cat dog elephant mussel cow horse canary baboon snake shark otherword" nil "word cat dog elephant mussel cow horse canary baboon snake shark otherword" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (509 "\"word cat dog elephant mussel cow horse canary baboon snake shark\" =~ /word (?:[a-zA-Z0-9]+ ){0,10}otherword/" "word (?:[a-zA-Z0-9]+ ){0,10}otherword" nil nil nil nil "word cat dog elephant mussel cow horse canary baboon snake shark" nil nil nil) (510 "\"word cat dog elephant mussel cow horse canary baboon snake shark the quick brown fox and the lazy dog and several other words getting close to thirty by now I hope\" =~ /word (?:[a-zA-Z0-9]+ ){0,300}otherword/" "word (?:[a-zA-Z0-9]+ ){0,300}otherword" nil nil nil nil "word cat dog elephant mussel cow horse canary baboon snake shark the quick brown fox and the lazy dog and several other words getting close to thirty by now I hope" nil nil nil) (511 "\"bcd\" =~ /^(a){0,0}/" "^(a){0,0}" nil nil nil nil "bcd" nil "" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (512 "\"abc\" =~ /^(a){0,0}/" "^(a){0,0}" nil nil nil nil "abc" nil "" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (513 "\"aab\" =~ /^(a){0,0}/" "^(a){0,0}" nil nil nil nil "aab" nil "" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (514 "\"bcd\" =~ /^(a){0,1}/" "^(a){0,1}" nil nil nil nil "bcd" nil "" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (515 "\"abc\" =~ /^(a){0,1}/" "^(a){0,1}" nil nil nil nil "abc" nil "a" ("a" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (516 "\"aab\" =~ /^(a){0,1}/" "^(a){0,1}" nil nil nil nil "aab" nil "a" ("a" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (517 "\"bcd\" =~ /^(a){0,2}/" "^(a){0,2}" nil nil nil nil "bcd" nil "" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (518 "\"abc\" =~ /^(a){0,2}/" "^(a){0,2}" nil nil nil nil "abc" nil "a" ("a" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (519 "\"aab\" =~ /^(a){0,2}/" "^(a){0,2}" nil nil nil nil "aab" nil "aa" ("a" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (520 "\"bcd\" =~ /^(a){0,3}/" "^(a){0,3}" nil nil nil nil "bcd" nil "" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (521 "\"abc\" =~ /^(a){0,3}/" "^(a){0,3}" nil nil nil nil "abc" nil "a" ("a" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (522 "\"aab\" =~ /^(a){0,3}/" "^(a){0,3}" nil nil nil nil "aab" nil "aa" ("a" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (523 "\"aaa\" =~ /^(a){0,3}/" "^(a){0,3}" nil nil nil nil "aaa" nil "aaa" ("a" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (524 "\"bcd\" =~ /^(a){0,}/" "^(a){0,}" nil nil nil nil "bcd" nil "" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (525 "\"abc\" =~ /^(a){0,}/" "^(a){0,}" nil nil nil nil "abc" nil "a" ("a" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (526 "\"aab\" =~ /^(a){0,}/" "^(a){0,}" nil nil nil nil "aab" nil "aa" ("a" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (527 "\"aaa\" =~ /^(a){0,}/" "^(a){0,}" nil nil nil nil "aaa" nil "aaa" ("a" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (528 "\"aaaaaaaa\" =~ /^(a){0,}/" "^(a){0,}" nil nil nil nil "aaaaaaaa" nil "aaaaaaaa" ("a" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (529 "\"bcd\" =~ /^(a){1,1}/" "^(a){1,1}" nil nil nil nil "bcd" nil nil nil) (530 "\"abc\" =~ /^(a){1,1}/" "^(a){1,1}" nil nil nil nil "abc" nil "a" ("a" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (531 "\"aab\" =~ /^(a){1,1}/" "^(a){1,1}" nil nil nil nil "aab" nil "a" ("a" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (532 "\"bcd\" =~ /^(a){1,2}/" "^(a){1,2}" nil nil nil nil "bcd" nil nil nil) (533 "\"abc\" =~ /^(a){1,2}/" "^(a){1,2}" nil nil nil nil "abc" nil "a" ("a" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (534 "\"aab\" =~ /^(a){1,2}/" "^(a){1,2}" nil nil nil nil "aab" nil "aa" ("a" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (535 "\"bcd\" =~ /^(a){1,3}/" "^(a){1,3}" nil nil nil nil "bcd" nil nil nil) (536 "\"abc\" =~ /^(a){1,3}/" "^(a){1,3}" nil nil nil nil "abc" nil "a" ("a" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (537 "\"aab\" =~ /^(a){1,3}/" "^(a){1,3}" nil nil nil nil "aab" nil "aa" ("a" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (538 "\"aaa\" =~ /^(a){1,3}/" "^(a){1,3}" nil nil nil nil "aaa" nil "aaa" ("a" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (539 "\"bcd\" =~ /^(a){1,}/" "^(a){1,}" nil nil nil nil "bcd" nil nil nil) (540 "\"abc\" =~ /^(a){1,}/" "^(a){1,}" nil nil nil nil "abc" nil "a" ("a" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (541 "\"aab\" =~ /^(a){1,}/" "^(a){1,}" nil nil nil nil "aab" nil "aa" ("a" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (542 "\"aaa\" =~ /^(a){1,}/" "^(a){1,}" nil nil nil nil "aaa" nil "aaa" ("a" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (543 "\"aaaaaaaa\" =~ /^(a){1,}/" "^(a){1,}" nil nil nil nil "aaaaaaaa" nil "aaaaaaaa" ("a" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (544 "\"borfle\\nbib.gif\\nno\" =~ /.*\\.gif/" ".*\\.gif" nil nil nil nil "borfle bib.gif no" nil "bib.gif" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (545 "\"borfle\\nbib.gif\\nno\" =~ /.{0,}\\.gif/" ".{0,}\\.gif" nil nil nil nil "borfle bib.gif no" nil "bib.gif" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (546 "\"borfle\\nbib.gif\\nno\" =~ /.*\\.gif/m" ".*\\.gif" nil t nil nil "borfle bib.gif no" nil "bib.gif" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (547 "\"borfle\\nbib.gif\\nno\" =~ /.*\\.gif/s" ".*\\.gif" nil nil t nil "borfle bib.gif no" nil "borfle bib.gif" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (548 "\"borfle\\nbib.gif\\nno\" =~ /.*\\.gif/ms" ".*\\.gif" nil t t nil "borfle bib.gif no" nil "borfle bib.gif" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (549 "\"borfle\\nbib.gif\\nno\" =~ /.*$/" ".*$" nil nil nil nil "borfle bib.gif no" nil "no" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (550 "\"borfle\\nbib.gif\\nno\" =~ /.*$/m" ".*$" nil t nil nil "borfle bib.gif no" nil "borfle" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (551 "\"borfle\\nbib.gif\\nno\" =~ /.*$/s" ".*$" nil nil t nil "borfle bib.gif no" nil "borfle bib.gif no" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (552 "\"borfle\\nbib.gif\\nno\" =~ /.*$/ms" ".*$" nil t t nil "borfle bib.gif no" nil "borfle bib.gif no" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (553 "\"borfle\\nbib.gif\\nno\\n\" =~ /.*$/" ".*$" nil nil nil nil "borfle bib.gif no " nil "no" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (554 "\"borfle\\nbib.gif\\nno\\n\" =~ /.*$/m" ".*$" nil t nil nil "borfle bib.gif no " nil "borfle" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (555 "\"borfle\\nbib.gif\\nno\\n\" =~ /.*$/s" ".*$" nil nil t nil "borfle bib.gif no " nil "borfle bib.gif no " (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (556 "\"borfle\\nbib.gif\\nno\\n\" =~ /.*$/ms" ".*$" nil t t nil "borfle bib.gif no " nil "borfle bib.gif no " (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (557 "\"abcde\\n1234Xyz\" =~ /(.*X|^B)/" "(.*X|^B)" nil nil nil nil "abcde 1234Xyz" nil "1234X" ("1234X" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (558 "\"BarFoo\" =~ /(.*X|^B)/" "(.*X|^B)" nil nil nil nil "BarFoo" nil "B" ("B" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (559 "\"abcde\\nBar\" =~ /(.*X|^B)/" "(.*X|^B)" nil nil nil nil "abcde Bar" nil nil nil) (560 "\"abcde\\n1234Xyz\" =~ /(.*X|^B)/m" "(.*X|^B)" nil t nil nil "abcde 1234Xyz" nil "1234X" ("1234X" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (561 "\"BarFoo\" =~ /(.*X|^B)/m" "(.*X|^B)" nil t nil nil "BarFoo" nil "B" ("B" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (562 "\"abcde\\nBar\" =~ /(.*X|^B)/m" "(.*X|^B)" nil t nil nil "abcde Bar" nil "B" ("B" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (563 "\"abcde\\n1234Xyz\" =~ /(.*X|^B)/s" "(.*X|^B)" nil nil t nil "abcde 1234Xyz" nil "abcde 1234X" ("abcde 1234X" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (564 "\"BarFoo\" =~ /(.*X|^B)/s" "(.*X|^B)" nil nil t nil "BarFoo" nil "B" ("B" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (565 "\"abcde\\nBar\" =~ /(.*X|^B)/s" "(.*X|^B)" nil nil t nil "abcde Bar" nil nil nil) (566 "\"abcde\\n1234Xyz\" =~ /(.*X|^B)/ms" "(.*X|^B)" nil t t nil "abcde 1234Xyz" nil "abcde 1234X" ("abcde 1234X" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (567 "\"BarFoo\" =~ /(.*X|^B)/ms" "(.*X|^B)" nil t t nil "BarFoo" nil "B" ("B" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (568 "\"abcde\\nBar\" =~ /(.*X|^B)/ms" "(.*X|^B)" nil t t nil "abcde Bar" nil "B" ("B" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (569 "\"abcde\\n1234Xyz\" =~ /(?s)(.*X|^B)/" "(?s)(.*X|^B)" nil nil nil nil "abcde 1234Xyz" nil "abcde 1234X" ("abcde 1234X" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (570 "\"BarFoo\" =~ /(?s)(.*X|^B)/" "(?s)(.*X|^B)" nil nil nil nil "BarFoo" nil "B" ("B" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (571 "\"abcde\\nBar\" =~ /(?s)(.*X|^B)/" "(?s)(.*X|^B)" nil nil nil nil "abcde Bar" nil nil nil) (572 "\"abcde\\n1234Xyz\" =~ /(?s:.*X|^B)/" "(?s:.*X|^B)" nil nil nil nil "abcde 1234Xyz" nil "abcde 1234X" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (573 "\"BarFoo\" =~ /(?s:.*X|^B)/" "(?s:.*X|^B)" nil nil nil nil "BarFoo" nil "B" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (574 "\"abcde\\nBar\" =~ /(?s:.*X|^B)/" "(?s:.*X|^B)" nil nil nil nil "abcde Bar" nil nil nil) (575 "\"abc\\nB\" =~ /^.*B/" "^.*B" nil nil nil nil "abc B" nil nil nil) (576 "\"abc\\nB\" =~ /(?s)^.*B/" "(?s)^.*B" nil nil nil nil "abc B" nil "abc B" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (577 "\"abc\\nB\" =~ /(?m)^.*B/" "(?m)^.*B" nil nil nil nil "abc B" nil "B" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (578 "\"abc\\nB\" =~ /(?ms)^.*B/" "(?ms)^.*B" nil nil nil nil "abc B" nil "abc B" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (579 "\"abc\\nB\" =~ /(?ms)^B/" "(?ms)^B" nil nil nil nil "abc B" nil "B" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (580 "\"B\\n\" =~ /(?s)B$/" "(?s)B$" nil nil nil nil "B " nil "B" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (581 "\"123456654321\" =~ /^[0-9][0-9][0-9][0-9][0-9][0-9][0-9][0-9][0-9][0-9][0-9][0-9]/" "^[0-9][0-9][0-9][0-9][0-9][0-9][0-9][0-9][0-9][0-9][0-9][0-9]" nil nil nil nil "123456654321" nil "123456654321" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (582 "\"123456654321\" =~ /^\\d\\d\\d\\d\\d\\d\\d\\d\\d\\d\\d\\d/" "^\\d\\d\\d\\d\\d\\d\\d\\d\\d\\d\\d\\d" nil nil nil nil "123456654321" nil "123456654321" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (583 "\"123456654321\" =~ /^[\\d][\\d][\\d][\\d][\\d][\\d][\\d][\\d][\\d][\\d][\\d][\\d]/" "^[\\d][\\d][\\d][\\d][\\d][\\d][\\d][\\d][\\d][\\d][\\d][\\d]" nil nil nil nil "123456654321" nil "123456654321" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (584 "\"abcabcabcabc\" =~ /^[abc]{12}/" "^[abc]{12}" nil nil nil nil "abcabcabcabc" nil "abcabcabcabc" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (585 "\"abcabcabcabc\" =~ /^[a-c]{12}/" "^[a-c]{12}" nil nil nil nil "abcabcabcabc" nil "abcabcabcabc" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (586 "\"abcabcabcabc\" =~ /^(a|b|c){12}/" "^(a|b|c){12}" nil nil nil nil "abcabcabcabc" nil "abcabcabcabc" ("c" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (587 "\"n\" =~ /^[abcdefghijklmnopqrstuvwxy0123456789]/" "^[abcdefghijklmnopqrstuvwxy0123456789]" nil nil nil nil "n" nil "n" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (588 "\"z\" =~ /^[abcdefghijklmnopqrstuvwxy0123456789]/" "^[abcdefghijklmnopqrstuvwxy0123456789]" nil nil nil nil "z" nil nil nil) (589 "\"abcd\" =~ /abcde{0,0}/" "abcde{0,0}" nil nil nil nil "abcd" nil "abcd" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (590 "\"abce\" =~ /abcde{0,0}/" "abcde{0,0}" nil nil nil nil "abce" nil nil nil) (591 "\"abe\" =~ /ab[cd]{0,0}e/" "ab[cd]{0,0}e" nil nil nil nil "abe" nil "abe" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (592 "\"abcde\" =~ /ab[cd]{0,0}e/" "ab[cd]{0,0}e" nil nil nil nil "abcde" nil nil nil) (593 "\"abd\" =~ /ab(c){0,0}d/" "ab(c){0,0}d" nil nil nil nil "abd" nil "abd" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (594 "\"abcd\" =~ /ab(c){0,0}d/" "ab(c){0,0}d" nil nil nil nil "abcd" nil nil nil) (595 "\"a\" =~ /a(b*)/" "a(b*)" nil nil nil nil "a" nil "a" ("" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (596 "\"ab\" =~ /a(b*)/" "a(b*)" nil nil nil nil "ab" nil "ab" ("b" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (597 "\"abbbb\" =~ /a(b*)/" "a(b*)" nil nil nil nil "abbbb" nil "abbbb" ("bbbb" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (598 "\"bbbbb\" =~ /a(b*)/" "a(b*)" nil nil nil nil "bbbbb" nil nil nil) (599 "\"abe\" =~ /ab\\d{0}e/" "ab\\d{0}e" nil nil nil nil "abe" nil "abe" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (600 "\"ab1e\" =~ /ab\\d{0}e/" "ab\\d{0}e" nil nil nil nil "ab1e" nil nil nil) (601 "\"the \\\"quick\\\" brown fox\" =~ /\"([^\\\\\"]+|\\\\.)*\"/" "\"([^\\\\\"]+|\\\\.)*\"" nil nil nil nil "the \"quick\" brown fox" nil "\"quick\"" ("quick" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (602 "\"\\\"the \\\\\\\"quick\\\\\\\" brown fox\\\"\" =~ /\"([^\\\\\"]+|\\\\.)*\"/" "\"([^\\\\\"]+|\\\\.)*\"" nil nil nil nil "\"the \\\"quick\\\" brown fox\"" nil "\"the \\\"quick\\\" brown fox\"" (" brown fox" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (603 "\"abc\" =~ /.*?/" ".*?" nil nil nil nil "abc" nil "" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (604 "\"abc\" =~ /\\b/" "\\b" nil nil nil nil "abc" nil "" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (605 "\"abc\" =~ /\\b/" "\\b" nil nil nil nil "abc" nil "" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (606 "\"abc\" =~ /(?#)/" "" nil nil nil nil "abc" nil "" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (607 "\"43.Word Processor
(N-1286)
Lega lstaff.comCA - Statewide\" =~ /]{0,})>]{0,})>([\\d]{0,}\\.)(.*)((
([\\w\\W\\s\\d][^<>]{0,})|[\\s]{0,}))<\\/a><\\/TD>]{0,})>([\\w\\W\\s\\d][^<>]{0,})<\\/TD>]{0,})>([\\w\\W\\s\\d][^<>]{0,})<\\/TD><\\/TR>/is" "]{0,})>]{0,})>([\\d]{0,}\\.)(.*)((
([\\w\\W\\s\\d][^<>]{0,})|[\\s]{0,}))<\\/a><\\/TD>]{0,})>([\\w\\W\\s\\d][^<>]{0,})<\\/TD>]{0,})>([\\w\\W\\s\\d][^<>]{0,})<\\/TD><\\/TR>" t nil t nil "43.Word Processor
(N-1286)
Lega lstaff.comCA - Statewide" nil "43.Word Processor
(N-1286)
Lega lstaff.comCA - Statewide" (" BGCOLOR='#DBE9E9'" " align=left valign=top" "43." "Word Processor
(N-1286)" "" "" nil " align=left valign=top" "Lega lstaff.com" " align=left valign=top" "CA - Statewide" nil nil nil nil nil)) (608 "\"acb\" =~ /a[^a]b/" "a[^a]b" nil nil nil nil "acb" nil "acb" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (609 "\"a\\nb\" =~ /a[^a]b/" "a[^a]b" nil nil nil nil "a b" nil "a b" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (610 "\"acb\" =~ /a.b/" "a.b" nil nil nil nil "acb" nil "acb" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (611 "\"a\\nb\" =~ /a.b/" "a.b" nil nil nil nil "a b" nil nil nil) (612 "\"acb\" =~ /a[^a]b/s" "a[^a]b" nil nil t nil "acb" nil "acb" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (613 "\"a\\nb\" =~ /a[^a]b/s" "a[^a]b" nil nil t nil "a b" nil "a b" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (614 "\"acb\" =~ /a.b/s" "a.b" nil nil t nil "acb" nil "acb" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (615 "\"a\\nb\" =~ /a.b/s" "a.b" nil nil t nil "a b" nil "a b" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (616 "\"bac\" =~ /^(b+?|a){1,2}?c/" "^(b+?|a){1,2}?c" nil nil nil nil "bac" nil "bac" ("a" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (617 "\"bbac\" =~ /^(b+?|a){1,2}?c/" "^(b+?|a){1,2}?c" nil nil nil nil "bbac" nil "bbac" ("a" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (618 "\"bbbac\" =~ /^(b+?|a){1,2}?c/" "^(b+?|a){1,2}?c" nil nil nil nil "bbbac" nil "bbbac" ("a" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (619 "\"bbbbac\" =~ /^(b+?|a){1,2}?c/" "^(b+?|a){1,2}?c" nil nil nil nil "bbbbac" nil "bbbbac" ("a" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (620 "\"bbbbbac\" =~ /^(b+?|a){1,2}?c/" "^(b+?|a){1,2}?c" nil nil nil nil "bbbbbac" nil "bbbbbac" ("a" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (621 "\"bac\" =~ /^(b+|a){1,2}?c/" "^(b+|a){1,2}?c" nil nil nil nil "bac" nil "bac" ("a" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (622 "\"bbac\" =~ /^(b+|a){1,2}?c/" "^(b+|a){1,2}?c" nil nil nil nil "bbac" nil "bbac" ("a" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (623 "\"bbbac\" =~ /^(b+|a){1,2}?c/" "^(b+|a){1,2}?c" nil nil nil nil "bbbac" nil "bbbac" ("a" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (624 "\"bbbbac\" =~ /^(b+|a){1,2}?c/" "^(b+|a){1,2}?c" nil nil nil nil "bbbbac" nil "bbbbac" ("a" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (625 "\"bbbbbac\" =~ /^(b+|a){1,2}?c/" "^(b+|a){1,2}?c" nil nil nil nil "bbbbbac" nil "bbbbbac" ("a" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (626 "\"x\\nb\\n\" =~ /(?!\\A)x/m" "(?!\\A)x" nil t nil nil "x b " nil nil nil) (627 "\"a\\bx\\n\" =~ /(?!\\A)x/m" "(?!\\A)x" nil t nil nil ("a" 8 "x" 10) nil "x" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (628 "\"\\0{ab}\" =~ /\\x0{ab}/" "\\x0{ab}" nil nil nil nil ("" 0 "{ab}") nil ("" 0 "{ab}") (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (629 "\"CD\" =~ /(A|B)*?CD/" "(A|B)*?CD" nil nil nil nil "CD" nil "CD" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (630 "\"CD\" =~ /(A|B)*CD/" "(A|B)*CD" nil nil nil nil "CD" nil "CD" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (631 "\"ABABAB\" =~ /(AB)*?\\1/" "(AB)*?\\1" nil nil nil nil "ABABAB" nil "ABAB" ("AB" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (632 "\"ABABAB\" =~ /(AB)*\\1/" "(AB)*\\1" nil nil nil nil "ABABAB" nil "ABABAB" ("AB" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (633 "\"doesn't matter\" =~ /(/" "(" nil nil nil nil "doesn't matter" t nil nil) (634 "\"doesn't matter\" =~ /(x)\\2/" "(x)\\2" nil nil nil nil "doesn't matter" t nil nil) (635 "\"aaaaaaaaaac\" =~ /((a{0,5}){0,5}){0,5}[c]/" "((a{0,5}){0,5}){0,5}[c]" nil nil nil nil "aaaaaaaaaac" nil "aaaaaaaaaac" ("" "" nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (636 "\"aaaaaaaaaa\" =~ /((a{0,5}){0,5}){0,5}[c]/" "((a{0,5}){0,5}){0,5}[c]" nil nil nil nil "aaaaaaaaaa" nil nil nil) (637 "\"aaaaaaaaaac\" =~ /((a{0,5}){0,5})*[c]/" "((a{0,5}){0,5})*[c]" nil nil nil nil "aaaaaaaaaac" nil "aaaaaaaaaac" ("" "" nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (638 "\"aaaaaaaaaa\" =~ /((a{0,5}){0,5})*[c]/" "((a{0,5}){0,5})*[c]" nil nil nil nil "aaaaaaaaaa" nil nil nil) (639 "\"a\" =~ /(\\b)*a/" "(\\b)*a" nil nil nil nil "a" nil "a" ("" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (640 "\"ab\" =~ /(a)*b/" "(a)*b" nil nil nil nil "ab" nil "ab" ("a" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (641 "\"ab\" =~ /(a|)*b/" "(a|)*b" nil nil nil nil "ab" nil "ab" ("" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (642 "\"b\" =~ /(a|)*b/" "(a|)*b" nil nil nil nil "b" nil "b" ("" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (643 "\"x\" =~ /(a|)*b/" "(a|)*b" nil nil nil nil "x" nil nil nil) (644 "\"abab\" =~ /^(?:(a)|(b))*\\1\\2$/" "^(?:(a)|(b))*\\1\\2$" nil nil nil nil "abab" nil "abab" ("a" "b" nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (645 "\"abcxabcydef\" =~ /abc[^x]def/" "abc[^x]def" nil nil nil nil "abcxabcydef" nil "abcydef" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (646 "\"aax\" =~ /^(a|\\1x)*$/" "^(a|\\1x)*$" nil nil nil nil "aax" nil "aax" ("ax" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (647 "\"aaxa\" =~ /^(a|\\1x)*$/" "^(a|\\1x)*$" nil nil nil nil "aaxa" nil "aaxa" ("a" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (648 "\"@{['']}\" =~ /(?#)/" "" nil nil nil nil "" nil "" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (649 "\"ab\" =~ /^(?:(a)|(b))*$/" "^(?:(a)|(b))*$" nil nil nil nil "ab" nil "ab" ("a" "b" nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (650 "\"a\" =~ /[\\0]/" "[\\0]" nil nil nil nil "a" nil nil nil) (651 "\"\\0\" =~ /[\\0]/" "[\\0]" nil nil nil nil ("" 0) nil ("" 0) (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (652 "\"a\" =~ /[\\1]/" "[\\1]" nil nil nil nil "a" nil nil nil) (653 "\"\\1\" =~ /[\\1]/" "[\\1]" nil nil nil nil ("" 1) nil ("" 1) (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (654 "\"doesn't matter\" =~ /\\10()()()()()()()()()/" "\\10()()()()()()()()()" nil nil nil nil "doesn't matter" nil nil nil) (655 "\"a\" =~ /\\10()()()()()()()()()()/" "\\10()()()()()()()()()()" nil nil nil nil "a" nil nil nil) (656 "\"ab\" =~ /a(?<)b/" "a(?<)b" nil nil nil nil "ab" nil "ab" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (657 "\"doesn't matter\" =~ /[]/" "[]" nil nil nil nil "doesn't matter" t nil nil) (658 "\"doesn't matter\" =~ /[\\]/" "[\\]" nil nil nil nil "doesn't matter" t nil nil) (659 "\"a\" =~ /()/" "()" nil nil nil nil "a" nil "" ("" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (660 "\"x\" =~ /[\\x]/" "[\\x]" nil nil nil nil "x" nil nil nil) (661 "\"\\0\" =~ /[\\x]/" "[\\x]" nil nil nil nil ("" 0) nil ("" 0) (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (662 "\"a\" =~ /((a)*)*/" "((a)*)*" nil nil nil nil "a" nil "a" ("" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (663 "\"a\" =~ /()a\\1/" "()a\\1" nil nil nil nil "a" nil "a" ("" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (664 "\"a\" =~ /a\\1()/" "a\\1()" nil nil nil nil "a" nil nil nil) (665 "\"aaa\" =~ /a(?i)a(?-i)a/" "a(?i)a(?-i)a" nil nil nil nil "aaa" nil "aaa" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (666 "\"aAa\" =~ /a(?i)a(?-i)a/" "a(?i)a(?-i)a" nil nil nil nil "aAa" nil "aAa" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (667 "\"aAA\" =~ /a(?i)a(?-i)a/" "a(?i)a(?-i)a" nil nil nil nil "aAA" nil nil nil) (668 "\"aaaaa\" =~ /a(?i)a(?-i)a(?i)a(?-i)a/" "a(?i)a(?-i)a(?i)a(?-i)a" nil nil nil nil "aaaaa" nil "aaaaa" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (669 "\"aAaAa\" =~ /a(?i)a(?-i)a(?i)a(?-i)a/" "a(?i)a(?-i)a(?i)a(?-i)a" nil nil nil nil "aAaAa" nil "aAaAa" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (670 "\"AaAaA\" =~ /a(?i)a(?-i)a(?i)a(?-i)a/" "a(?i)a(?-i)a(?i)a(?-i)a" nil nil nil nil "AaAaA" nil nil nil) (671 "\"aAAAa\" =~ /a(?i)a(?-i)a(?i)a(?-i)a/" "a(?i)a(?-i)a(?i)a(?-i)a" nil nil nil nil "aAAAa" nil nil nil) (672 "\"AaaaA\" =~ /a(?i)a(?-i)a(?i)a(?-i)a/" "a(?i)a(?-i)a(?i)a(?-i)a" nil nil nil nil "AaaaA" nil nil nil) (673 "\"AAAAA\" =~ /a(?i)a(?-i)a(?i)a(?-i)a/" "a(?i)a(?-i)a(?i)a(?-i)a" nil nil nil nil "AAAAA" nil nil nil) (674 "\"aaAAA\" =~ /a(?i)a(?-i)a(?i)a(?-i)a/" "a(?i)a(?-i)a(?i)a(?-i)a" nil nil nil nil "aaAAA" nil nil nil) (675 "\"AAaaa\" =~ /a(?i)a(?-i)a(?i)a(?-i)a/" "a(?i)a(?-i)a(?i)a(?-i)a" nil nil nil nil "AAaaa" nil nil nil) (676 "\"a\" =~ /\\x/" "\\x" nil nil nil nil "a" nil nil nil) (677 "\"X\" =~ /\\x/" "\\x" nil nil nil nil "X" nil nil nil) (678 "\"\\0\" =~ /\\x/" "\\x" nil nil nil nil ("" 0) nil ("" 0) (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (679 "\"a\" =~ /[a-c-e]/" "[a-c-e]" nil nil nil nil "a" nil "a" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (680 "\"b\" =~ /[a-c-e]/" "[a-c-e]" nil nil nil nil "b" nil "b" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (681 "\"d\" =~ /[a-c-e]/" "[a-c-e]" nil nil nil nil "d" nil nil nil) (682 "\"-\" =~ /[a-c-e]/" "[a-c-e]" nil nil nil nil "-" nil "-" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (683 "\"b\" =~ /[b-\\d]/" "[b-\\d]" nil nil nil nil "b" nil "b" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (684 "\"c\" =~ /[b-\\d]/" "[b-\\d]" nil nil nil nil "c" nil nil nil) (685 "\"d\" =~ /[b-\\d]/" "[b-\\d]" nil nil nil nil "d" nil nil nil) (686 "\"-\" =~ /[b-\\d]/" "[b-\\d]" nil nil nil nil "-" nil "-" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (687 "\"1\" =~ /[b-\\d]/" "[b-\\d]" nil nil nil nil "1" nil "1" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (688 "\"d\" =~ /[\\d-f]/" "[\\d-f]" nil nil nil nil "d" nil nil nil) (689 "\"e\" =~ /[\\d-f]/" "[\\d-f]" nil nil nil nil "e" nil nil nil) (690 "\"f\" =~ /[\\d-f]/" "[\\d-f]" nil nil nil nil "f" nil "f" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (691 "\"-\" =~ /[\\d-f]/" "[\\d-f]" nil nil nil nil "-" nil "-" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (692 "\"1\" =~ /[\\d-f]/" "[\\d-f]" nil nil nil nil "1" nil "1" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (693 "\"doesn't matter\" =~ /[/" "[" nil nil nil nil "doesn't matter" t nil nil) (694 "\"]\" =~ /]/" "]" nil nil nil nil "]" nil "]" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (695 "\"a\" =~ /]/" "]" nil nil nil nil "a" nil nil nil) (696 "\"doesn't matter\" =~ /[]/" "[]" nil nil nil nil "doesn't matter" t nil nil) (697 "\"-\" =~ /[-a-c]/" "[-a-c]" nil nil nil nil "-" nil "-" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (698 "\"a\" =~ /[-a-c]/" "[-a-c]" nil nil nil nil "a" nil "a" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (699 "\"b\" =~ /[-a-c]/" "[-a-c]" nil nil nil nil "b" nil "b" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (700 "\"d\" =~ /[-a-c]/" "[-a-c]" nil nil nil nil "d" nil nil nil) (701 "\"-\" =~ /[a-c-]/" "[a-c-]" nil nil nil nil "-" nil "-" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (702 "\"a\" =~ /[a-c-]/" "[a-c-]" nil nil nil nil "a" nil "a" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (703 "\"b\" =~ /[a-c-]/" "[a-c-]" nil nil nil nil "b" nil "b" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (704 "\"d\" =~ /[a-c-]/" "[a-c-]" nil nil nil nil "d" nil nil nil) (705 "\"a\" =~ /[-]/" "[-]" nil nil nil nil "a" nil nil nil) (706 "\"-\" =~ /[-]/" "[-]" nil nil nil nil "-" nil "-" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (707 "\"a\" =~ /[--]/" "[--]" nil nil nil nil "a" nil nil nil) (708 "\"-\" =~ /[--]/" "[--]" nil nil nil nil "-" nil "-" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (709 "\"a\" =~ /[---]/" "[---]" nil nil nil nil "a" nil nil nil) (710 "\"-\" =~ /[---]/" "[---]" nil nil nil nil "-" nil "-" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (711 "\"-\" =~ /[--b]/" "[--b]" nil nil nil nil "-" nil "-" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (712 "\"a\" =~ /[--b]/" "[--b]" nil nil nil nil "a" nil "a" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (713 "\"c\" =~ /[--b]/" "[--b]" nil nil nil nil "c" nil nil nil) (714 "\"doesn't matter\" =~ /[b--]/" "[b--]" nil nil nil nil "doesn't matter" t nil nil) (715 "\"a{\" =~ /a{/" "a{" nil nil nil nil "a{" nil "a{" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (716 "\"a{}\" =~ /a{}/" "a{}" nil nil nil nil "a{}" nil "a{}" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (717 "\"a{3\" =~ /a{3/" "a{3" nil nil nil nil "a{3" nil "a{3" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (718 "\"a{3,\" =~ /a{3,/" "a{3," nil nil nil nil "a{3," nil "a{3," (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (719 "\"a{3,3}\" =~ /a{3, 3}/" "a{3, 3}" nil nil nil nil "a{3,3}" nil nil nil) (720 "\"a{3, 3}\" =~ /a{3, 3}/" "a{3, 3}" nil nil nil nil "a{3, 3}" nil "a{3, 3}" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (721 "\"aaa\" =~ /a{3, 3}/" "a{3, 3}" nil nil nil nil "aaa" nil nil nil) (722 "\"a{3,3}\" =~ /a{3, 3}/x" "a{3, 3}" nil nil nil t "a{3,3}" nil "a{3,3}" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (723 "\"a{3, 3}\" =~ /a{3, 3}/x" "a{3, 3}" nil nil nil t "a{3, 3}" nil nil nil) (724 "\"aaa\" =~ /a{3, 3}/x" "a{3, 3}" nil nil nil t "aaa" nil nil nil) (725 "\"a{3,}\" =~ /a{3, }/" "a{3, }" nil nil nil nil "a{3,}" nil nil nil) (726 "\"a{3, }\" =~ /a{3, }/" "a{3, }" nil nil nil nil "a{3, }" nil "a{3, }" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (727 "\"aaa\" =~ /a{3, }/" "a{3, }" nil nil nil nil "aaa" nil nil nil) (728 "\"a{3,}\" =~ /a{3, }/x" "a{3, }" nil nil nil t "a{3,}" nil "a{3,}" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (729 "\"a{3, }\" =~ /a{3, }/x" "a{3, }" nil nil nil t "a{3, }" nil nil nil) (730 "\"aaa\" =~ /a{3, }/x" "a{3, }" nil nil nil t "aaa" nil nil nil) (731 "\"\\0 x\" =~ /\\x x/" "\\x x" nil nil nil nil ("" 0 " x") nil ("" 0 " x") (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (732 "\"\\0x\" =~ /\\x x/" "\\x x" nil nil nil nil ("" 0 "x") nil nil nil) (733 "\"\\0 x\" =~ /\\x x/x" "\\x x" nil nil nil t ("" 0 " x") nil nil nil) (734 "\"\\0x\" =~ /\\x x/x" "\\x x" nil nil nil t ("" 0 "x") nil ("" 0 "x") (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (735 "\"\\0003\" =~ /\\x 3/" "\\x 3" nil nil nil nil ("" 0 "3") nil nil nil) (736 "\"\\000 3\" =~ /\\x 3/" "\\x 3" nil nil nil nil ("" 0 " 3") nil ("" 0 " 3") (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (737 "\"x3\" =~ /\\x 3/" "\\x 3" nil nil nil nil "x3" nil nil nil) (738 "\"x 3\" =~ /\\x 3/" "\\x 3" nil nil nil nil "x 3" nil nil nil) (739 "\"\\0003\" =~ /\\x 3/x" "\\x 3" nil nil nil t ("" 0 "3") nil ("" 0 "3") (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (740 "\"\\000 3\" =~ /\\x 3/x" "\\x 3" nil nil nil t ("" 0 " 3") nil nil nil) (741 "\"x3\" =~ /\\x 3/x" "\\x 3" nil nil nil t "x3" nil nil nil) (742 "\"x 3\" =~ /\\x 3/x" "\\x 3" nil nil nil t "x 3" nil nil nil) (743 "\"a\" =~ /^a{ 1}$/" "^a{ 1}$" nil nil nil nil "a" nil nil nil) (744 "\"a{ 1}\" =~ /^a{ 1}$/" "^a{ 1}$" nil nil nil nil "a{ 1}" nil "a{ 1}" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (745 "\"a{1}\" =~ /^a{ 1}$/" "^a{ 1}$" nil nil nil nil "a{1}" nil nil nil) (746 "\"a\" =~ /^a{ 1}$/x" "^a{ 1}$" nil nil nil t "a" nil nil nil) (747 "\"a{ 1}\" =~ /^a{ 1}$/x" "^a{ 1}$" nil nil nil t "a{ 1}" nil nil nil) (748 "\"a{1}\" =~ /^a{ 1}$/x" "^a{ 1}$" nil nil nil t "a{1}" nil "a{1}" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (749 "\"{}\" =~ /{}/" "{}" nil nil nil nil "{}" nil "{}" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (750 "\"a\" =~ /{}/" "{}" nil nil nil nil "a" nil nil nil) (751 "\"doesn't matter\" =~ /{1}/" "{1}" nil nil nil nil "doesn't matter" t nil nil) (752 "\"doesn't matter\" =~ /*/" "*" nil nil nil nil "doesn't matter" t nil nil) (753 "\"x\" =~ /|/" "|" nil nil nil nil "x" nil "" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (754 "\"\\0000\" =~ /\\0000/" "\\0000" nil nil nil nil ("" 0 "0") nil ("" 0 "0") (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (755 "\"ab\" =~ /a(?<)b/" "a(?<)b" nil nil nil nil "ab" nil "ab" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (756 "\"ab\" =~ /a(?i)b/" "a(?i)b" nil nil nil nil "ab" nil "ab" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (757 "\"aB\" =~ /a(?i)b/" "a(?i)b" nil nil nil nil "aB" nil "aB" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (758 "\"Ab\" =~ /a(?i)b/" "a(?i)b" nil nil nil nil "Ab" nil nil nil) (759 "\"doesn't matter\" =~ /a(?i=a)/" "a(?i=a)" nil nil nil nil "doesn't matter" t nil nil) (760 "\"aa\" =~ /a(?<=a){3000}a/" "a(?<=a){3000}a" nil nil nil nil "aa" nil "aa" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (761 "\"xa\" =~ /a(?<=a){3000}a/" "a(?<=a){3000}a" nil nil nil nil "xa" nil nil nil) (762 "\"ax\" =~ /a(?<=a){3000}a/" "a(?<=a){3000}a" nil nil nil nil "ax" nil nil nil) (763 "\"aa\" =~ /a(?!=a){3000}a/" "a(?!=a){3000}a" nil nil nil nil "aa" nil "aa" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (764 "\"ax\" =~ /a(?!=a){3000}a/" "a(?!=a){3000}a" nil nil nil nil "ax" nil nil nil) (765 "\"xa\" =~ /a(?!=a){3000}a/" "a(?!=a){3000}a" nil nil nil nil "xa" nil nil nil) (766 "\"aa\" =~ /a(){3000}a/" "a(){3000}a" nil nil nil nil "aa" nil "aa" ("" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (767 "\"ax\" =~ /a(){3000}a/" "a(){3000}a" nil nil nil nil "ax" nil nil nil) (768 "\"xa\" =~ /a(){3000}a/" "a(){3000}a" nil nil nil nil "xa" nil nil nil) (769 "\"aa\" =~ /a(?:){3000}a/" "a(?:){3000}a" nil nil nil nil "aa" nil "aa" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (770 "\"ax\" =~ /a(?:){3000}a/" "a(?:){3000}a" nil nil nil nil "ax" nil nil nil) (771 "\"aa\" =~ /a(?<=a)*a/" "a(?<=a)*a" nil nil nil nil "aa" nil "aa" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (772 "\"ax\" =~ /a(?<=a)*a/" "a(?<=a)*a" nil nil nil nil "ax" nil nil nil) (773 "\"xa\" =~ /a(?<=a)*a/" "a(?<=a)*a" nil nil nil nil "xa" nil nil nil) (774 "\"aa\" =~ /a(?!=a)*a/" "a(?!=a)*a" nil nil nil nil "aa" nil "aa" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (775 "\"ax\" =~ /a(?!=a)*a/" "a(?!=a)*a" nil nil nil nil "ax" nil nil nil) (776 "\"xa\" =~ /a(?!=a)*a/" "a(?!=a)*a" nil nil nil nil "xa" nil nil nil) (777 "\"aa\" =~ /a()*a/" "a()*a" nil nil nil nil "aa" nil "aa" ("" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (778 "\"ax\" =~ /a()*a/" "a()*a" nil nil nil nil "ax" nil nil nil) (779 "\"xa\" =~ /a()*a/" "a()*a" nil nil nil nil "xa" nil nil nil) (780 "\"aa\" =~ /a(?:)*a/" "a(?:)*a" nil nil nil nil "aa" nil "aa" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (781 "\"ax\" =~ /a(?:)*a/" "a(?:)*a" nil nil nil nil "ax" nil nil nil) (782 "\"xa\" =~ /a(?:)*a/" "a(?:)*a" nil nil nil nil "xa" nil nil nil) (783 "\"aa\" =~ /x(?<=a)*a/" "x(?<=a)*a" nil nil nil nil "aa" nil nil nil) (784 "\"xa\" =~ /x(?<=a)*a/" "x(?<=a)*a" nil nil nil nil "xa" nil "xa" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (785 "\"ax\" =~ /x(?<=a)*a/" "x(?<=a)*a" nil nil nil nil "ax" nil nil nil) (786 "\"aa\" =~ /a(?<=(a))*\\1/" "a(?<=(a))*\\1" nil nil nil nil "aa" nil "aa" ("a" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (787 "\"aa\" =~ /a(?<=(a))*?\\1/" "a(?<=(a))*?\\1" nil nil nil nil "aa" nil "aa" ("a" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (788 "\"aa\" =~ /(?=(a)\\1)*aa/" "(?=(a)\\1)*aa" nil nil nil nil "aa" nil "aa" ("a" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (789 "\"aaaaabbbbb\" =~ /^((a|b){2,5}){2}$/" "^((a|b){2,5}){2}$" nil nil nil nil "aaaaabbbbb" nil "aaaaabbbbb" ("bbbbb" "b" nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (790 "\"babc\" =~ /^(b*|ba){1,2}bc/" "^(b*|ba){1,2}bc" nil nil nil nil "babc" nil "babc" ("" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (791 "\"bbabc\" =~ /^(b*|ba){1,2}bc/" "^(b*|ba){1,2}bc" nil nil nil nil "bbabc" nil "bbabc" ("ba" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (792 "\"bababc\" =~ /^(b*|ba){1,2}bc/" "^(b*|ba){1,2}bc" nil nil nil nil "bababc" nil "bababc" ("ba" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (793 "\"bababbc\" =~ /^(b*|ba){1,2}bc/" "^(b*|ba){1,2}bc" nil nil nil nil "bababbc" nil nil nil) (794 "\"babababc\" =~ /^(b*|ba){1,2}bc/" "^(b*|ba){1,2}bc" nil nil nil nil "babababc" nil nil nil) (795 "\"aaaaac\" =~ /^a{4,5}(?:c|a)c$/" "^a{4,5}(?:c|a)c$" nil nil nil nil "aaaaac" nil "aaaaac" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (796 "\"aaaaaac\" =~ /^a{4,5}(?:c|a)c$/" "^a{4,5}(?:c|a)c$" nil nil nil nil "aaaaaac" nil "aaaaaac" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (797 "\"aaaaac\" =~ /^(a|){4,5}(?:c|a)c$/" "^(a|){4,5}(?:c|a)c$" nil nil nil nil "aaaaac" nil "aaaaac" ("" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (798 "\"aaaaaac\" =~ /^(a|){4,5}(?:c|a)c$/" "^(a|){4,5}(?:c|a)c$" nil nil nil nil "aaaaaac" nil "aaaaaac" ("a" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (799 "\"eeexabc\" =~ /(?m:^).abc$/" "(?m:^).abc$" nil nil nil nil "eeexabc" nil nil nil) (800 "\"eee\\nxabc\" =~ /(?m:^).abc$/" "(?m:^).abc$" nil nil nil nil "eee xabc" nil "xabc" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (801 "\"abc\" =~ /(?m:^)abc/" "(?m:^)abc" nil nil nil nil "abc" nil "abc" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (802 "\"\\nabc\" =~ /(?m:^)abc/" "(?m:^)abc" nil nil nil nil " abc" nil "abc" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (803 "\"abc\" =~ /^abc/" "^abc" nil nil nil nil "abc" nil "abc" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (804 "\"\\nabc\" =~ /^abc/" "^abc" nil nil nil nil " abc" nil nil nil) (805 "\"abc\" =~ /\\Aabc/" "\\Aabc" nil nil nil nil "abc" nil "abc" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (806 "\"\\nabc\" =~ /\\Aabc/" "\\Aabc" nil nil nil nil " abc" nil nil nil) (807 "\"foo\" =~ /(?.*/)foo\"" "(?>.*/)foo" nil nil nil nil "/this/is/a/very/long/line/in/deed/with/very/many/slashes/in/it/you/see/" nil nil nil) (826 "\"/this/is/a/very/long/line/in/deed/with/very/many/slashes/in/and/foo\" =~ \"(?>.*/)foo\"" "(?>.*/)foo" nil nil nil nil "/this/is/a/very/long/line/in/deed/with/very/many/slashes/in/and/foo" nil "/this/is/a/very/long/line/in/deed/with/very/many/slashes/in/and/foo" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (827 "\"1.230003938\" =~ /(?>(\\.\\d\\d[1-9]?))\\d+/" "(?>(\\.\\d\\d[1-9]?))\\d+" nil nil nil nil "1.230003938" nil ".230003938" (".23" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (828 "\"1.875000282\" =~ /(?>(\\.\\d\\d[1-9]?))\\d+/" "(?>(\\.\\d\\d[1-9]?))\\d+" nil nil nil nil "1.875000282" nil ".875000282" (".875" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (829 "\"1.235\" =~ /(?>(\\.\\d\\d[1-9]?))\\d+/" "(?>(\\.\\d\\d[1-9]?))\\d+" nil nil nil nil "1.235" nil nil nil) (830 "\"now is the time for all good men to come to the aid of the party\" =~ /^((?>\\w+)|(?>\\s+))*$/" "^((?>\\w+)|(?>\\s+))*$" nil nil nil nil "now is the time for all good men to come to the aid of the party" nil "now is the time for all good men to come to the aid of the party" ("party" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (831 "\"this is not a line with only words and spaces!\" =~ /^((?>\\w+)|(?>\\s+))*$/" "^((?>\\w+)|(?>\\s+))*$" nil nil nil nil "this is not a line with only words and spaces!" nil nil nil) (832 "\"12345a\" =~ /(\\d+)(\\w)/" "(\\d+)(\\w)" nil nil nil nil "12345a" nil "12345a" ("12345" "a" nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (833 "\"12345+\" =~ /(\\d+)(\\w)/" "(\\d+)(\\w)" nil nil nil nil "12345+" nil "12345" ("1234" "5" nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (834 "\"12345a\" =~ /((?>\\d+))(\\w)/" "((?>\\d+))(\\w)" nil nil nil nil "12345a" nil "12345a" ("12345" "a" nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (835 "\"12345+\" =~ /((?>\\d+))(\\w)/" "((?>\\d+))(\\w)" nil nil nil nil "12345+" nil nil nil) (836 "\"aaab\" =~ /(?>a+)b/" "(?>a+)b" nil nil nil nil "aaab" nil "aaab" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (837 "\"aaab\" =~ /((?>a+)b)/" "((?>a+)b)" nil nil nil nil "aaab" nil "aaab" ("aaab" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (838 "\"aaab\" =~ /(?>(a+))b/" "(?>(a+))b" nil nil nil nil "aaab" nil "aaab" ("aaa" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (839 "\"aaabbbccc\" =~ /(?>b)+/" "(?>b)+" nil nil nil nil "aaabbbccc" nil "bbb" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (840 "\"aaabbbbccccd\" =~ /(?>a+|b+|c+)*c/" "(?>a+|b+|c+)*c" nil nil nil nil "aaabbbbccccd" nil "aaabbbbc" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (841 "\"((abc(ade)ufh()()x\" =~ /((?>[^()]+)|\\([^()]*\\))+/" "((?>[^()]+)|\\([^()]*\\))+" nil nil nil nil "((abc(ade)ufh()()x" nil "abc(ade)ufh()()x" ("x" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (842 "\"(abc)\" =~ /\\(((?>[^()]+)|\\([^()]+\\))+\\)/" "\\(((?>[^()]+)|\\([^()]+\\))+\\)" nil nil nil nil "(abc)" nil "(abc)" ("abc" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (843 "\"(abc(def)xyz)\" =~ /\\(((?>[^()]+)|\\([^()]+\\))+\\)/" "\\(((?>[^()]+)|\\([^()]+\\))+\\)" nil nil nil nil "(abc(def)xyz)" nil "(abc(def)xyz)" ("xyz" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (844 "\"((()aaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaa\" =~ /\\(((?>[^()]+)|\\([^()]+\\))+\\)/" "\\(((?>[^()]+)|\\([^()]+\\))+\\)" nil nil nil nil "((()aaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaa" nil nil nil) (845 "\"ab\" =~ /a(?-i)b/i" "a(?-i)b" t nil nil nil "ab" nil "ab" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (846 "\"Ab\" =~ /a(?-i)b/i" "a(?-i)b" t nil nil nil "Ab" nil "Ab" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (847 "\"aB\" =~ /a(?-i)b/i" "a(?-i)b" t nil nil nil "aB" nil nil nil) (848 "\"AB\" =~ /a(?-i)b/i" "a(?-i)b" t nil nil nil "AB" nil nil nil) (849 "\"a bcd e\" =~ /(a (?x)b c)d e/" "(a (?x)b c)d e" nil nil nil nil "a bcd e" nil "a bcd e" ("a bc" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (850 "\"a b cd e\" =~ /(a (?x)b c)d e/" "(a (?x)b c)d e" nil nil nil nil "a b cd e" nil nil nil) (851 "\"abcd e\" =~ /(a (?x)b c)d e/" "(a (?x)b c)d e" nil nil nil nil "abcd e" nil nil nil) (852 "\"a bcde\" =~ /(a (?x)b c)d e/" "(a (?x)b c)d e" nil nil nil nil "a bcde" nil nil nil) (853 "\"a bcde f\" =~ /(a b(?x)c d (?-x)e f)/" "(a b(?x)c d (?-x)e f)" nil nil nil nil "a bcde f" nil "a bcde f" ("a bcde f" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (854 "\"abcdef\" =~ /(a b(?x)c d (?-x)e f)/" "(a b(?x)c d (?-x)e f)" nil nil nil nil "abcdef" nil nil nil) (855 "\"abc\" =~ /(a(?i)b)c/" "(a(?i)b)c" nil nil nil nil "abc" nil "abc" ("ab" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (856 "\"aBc\" =~ /(a(?i)b)c/" "(a(?i)b)c" nil nil nil nil "aBc" nil "aBc" ("aB" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (857 "\"abC\" =~ /(a(?i)b)c/" "(a(?i)b)c" nil nil nil nil "abC" nil nil nil) (858 "\"aBC\" =~ /(a(?i)b)c/" "(a(?i)b)c" nil nil nil nil "aBC" nil nil nil) (859 "\"Abc\" =~ /(a(?i)b)c/" "(a(?i)b)c" nil nil nil nil "Abc" nil nil nil) (860 "\"ABc\" =~ /(a(?i)b)c/" "(a(?i)b)c" nil nil nil nil "ABc" nil nil nil) (861 "\"ABC\" =~ /(a(?i)b)c/" "(a(?i)b)c" nil nil nil nil "ABC" nil nil nil) (862 "\"AbC\" =~ /(a(?i)b)c/" "(a(?i)b)c" nil nil nil nil "AbC" nil nil nil) (863 "\"abc\" =~ /a(?i:b)c/" "a(?i:b)c" nil nil nil nil "abc" nil "abc" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (864 "\"aBc\" =~ /a(?i:b)c/" "a(?i:b)c" nil nil nil nil "aBc" nil "aBc" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (865 "\"ABC\" =~ /a(?i:b)c/" "a(?i:b)c" nil nil nil nil "ABC" nil nil nil) (866 "\"abC\" =~ /a(?i:b)c/" "a(?i:b)c" nil nil nil nil "abC" nil nil nil) (867 "\"aBC\" =~ /a(?i:b)c/" "a(?i:b)c" nil nil nil nil "aBC" nil nil nil) (868 "\"aBc\" =~ /a(?i:b)*c/" "a(?i:b)*c" nil nil nil nil "aBc" nil "aBc" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (869 "\"aBBc\" =~ /a(?i:b)*c/" "a(?i:b)*c" nil nil nil nil "aBBc" nil "aBBc" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (870 "\"aBC\" =~ /a(?i:b)*c/" "a(?i:b)*c" nil nil nil nil "aBC" nil nil nil) (871 "\"aBBC\" =~ /a(?i:b)*c/" "a(?i:b)*c" nil nil nil nil "aBBC" nil nil nil) (872 "\"abcd\" =~ /a(?=b(?i)c)\\w\\wd/" "a(?=b(?i)c)\\w\\wd" nil nil nil nil "abcd" nil "abcd" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (873 "\"abCd\" =~ /a(?=b(?i)c)\\w\\wd/" "a(?=b(?i)c)\\w\\wd" nil nil nil nil "abCd" nil "abCd" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (874 "\"aBCd\" =~ /a(?=b(?i)c)\\w\\wd/" "a(?=b(?i)c)\\w\\wd" nil nil nil nil "aBCd" nil nil nil) (875 "\"abcD\" =~ /a(?=b(?i)c)\\w\\wd/" "a(?=b(?i)c)\\w\\wd" nil nil nil nil "abcD" nil nil nil) (876 "\"more than million\" =~ /(?s-i:more.*than).*million/i" "(?s-i:more.*than).*million" t nil nil nil "more than million" nil "more than million" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (877 "\"more than MILLION\" =~ /(?s-i:more.*than).*million/i" "(?s-i:more.*than).*million" t nil nil nil "more than MILLION" nil "more than MILLION" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (878 "\"more \\n than Million\" =~ /(?s-i:more.*than).*million/i" "(?s-i:more.*than).*million" t nil nil nil "more than Million" nil "more than Million" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (879 "\"MORE THAN MILLION\" =~ /(?s-i:more.*than).*million/i" "(?s-i:more.*than).*million" t nil nil nil "MORE THAN MILLION" nil nil nil) (880 "\"more \\n than \\n million\" =~ /(?s-i:more.*than).*million/i" "(?s-i:more.*than).*million" t nil nil nil "more than million" nil nil nil) (881 "\"more than million\" =~ /(?:(?s-i)more.*than).*million/i" "(?:(?s-i)more.*than).*million" t nil nil nil "more than million" nil "more than million" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (882 "\"more than MILLION\" =~ /(?:(?s-i)more.*than).*million/i" "(?:(?s-i)more.*than).*million" t nil nil nil "more than MILLION" nil "more than MILLION" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (883 "\"more \\n than Million\" =~ /(?:(?s-i)more.*than).*million/i" "(?:(?s-i)more.*than).*million" t nil nil nil "more than Million" nil "more than Million" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (884 "\"MORE THAN MILLION\" =~ /(?:(?s-i)more.*than).*million/i" "(?:(?s-i)more.*than).*million" t nil nil nil "MORE THAN MILLION" nil nil nil) (885 "\"more \\n than \\n million\" =~ /(?:(?s-i)more.*than).*million/i" "(?:(?s-i)more.*than).*million" t nil nil nil "more than million" nil nil nil) (886 "\"abc\" =~ /(?>a(?i)b+)+c/" "(?>a(?i)b+)+c" nil nil nil nil "abc" nil "abc" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (887 "\"aBbc\" =~ /(?>a(?i)b+)+c/" "(?>a(?i)b+)+c" nil nil nil nil "aBbc" nil "aBbc" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (888 "\"aBBc\" =~ /(?>a(?i)b+)+c/" "(?>a(?i)b+)+c" nil nil nil nil "aBBc" nil "aBBc" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (889 "\"Abc\" =~ /(?>a(?i)b+)+c/" "(?>a(?i)b+)+c" nil nil nil nil "Abc" nil nil nil) (890 "\"abAb\" =~ /(?>a(?i)b+)+c/" "(?>a(?i)b+)+c" nil nil nil nil "abAb" nil nil nil) (891 "\"abbC\" =~ /(?>a(?i)b+)+c/" "(?>a(?i)b+)+c" nil nil nil nil "abbC" nil nil nil) (892 "\"abc\" =~ /(?=a(?i)b)\\w\\wc/" "(?=a(?i)b)\\w\\wc" nil nil nil nil "abc" nil "abc" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (893 "\"aBc\" =~ /(?=a(?i)b)\\w\\wc/" "(?=a(?i)b)\\w\\wc" nil nil nil nil "aBc" nil "aBc" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (894 "\"Ab\" =~ /(?=a(?i)b)\\w\\wc/" "(?=a(?i)b)\\w\\wc" nil nil nil nil "Ab" nil nil nil) (895 "\"abC\" =~ /(?=a(?i)b)\\w\\wc/" "(?=a(?i)b)\\w\\wc" nil nil nil nil "abC" nil nil nil) (896 "\"aBC\" =~ /(?=a(?i)b)\\w\\wc/" "(?=a(?i)b)\\w\\wc" nil nil nil nil "aBC" nil nil nil) (897 "\"abxxc\" =~ /(?<=a(?i)b)(\\w\\w)c/" "(?<=a(?i)b)(\\w\\w)c" nil nil nil nil "abxxc" nil "xxc" ("xx" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (898 "\"aBxxc\" =~ /(?<=a(?i)b)(\\w\\w)c/" "(?<=a(?i)b)(\\w\\w)c" nil nil nil nil "aBxxc" nil "xxc" ("xx" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (899 "\"Abxxc\" =~ /(?<=a(?i)b)(\\w\\w)c/" "(?<=a(?i)b)(\\w\\w)c" nil nil nil nil "Abxxc" nil nil nil) (900 "\"ABxxc\" =~ /(?<=a(?i)b)(\\w\\w)c/" "(?<=a(?i)b)(\\w\\w)c" nil nil nil nil "ABxxc" nil nil nil) (901 "\"abxxC\" =~ /(?<=a(?i)b)(\\w\\w)c/" "(?<=a(?i)b)(\\w\\w)c" nil nil nil nil "abxxC" nil nil nil) (902 "\"aA\" =~ /(?:(a)|b)(?(1)A|B)/" "(?:(a)|b)(?(1)A|B)" nil nil nil nil "aA" nil "aA" ("a" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (903 "\"bB\" =~ /(?:(a)|b)(?(1)A|B)/" "(?:(a)|b)(?(1)A|B)" nil nil nil nil "bB" nil "bB" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (904 "\"aB\" =~ /(?:(a)|b)(?(1)A|B)/" "(?:(a)|b)(?(1)A|B)" nil nil nil nil "aB" nil nil nil) (905 "\"bA\" =~ /(?:(a)|b)(?(1)A|B)/" "(?:(a)|b)(?(1)A|B)" nil nil nil nil "bA" nil nil nil) (906 "\"aa\" =~ /^(a)?(?(1)a|b)+$/" "^(a)?(?(1)a|b)+$" nil nil nil nil "aa" nil "aa" ("a" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (907 "\"b\" =~ /^(a)?(?(1)a|b)+$/" "^(a)?(?(1)a|b)+$" nil nil nil nil "b" nil "b" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (908 "\"bb\" =~ /^(a)?(?(1)a|b)+$/" "^(a)?(?(1)a|b)+$" nil nil nil nil "bb" nil "bb" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (909 "\"ab\" =~ /^(a)?(?(1)a|b)+$/" "^(a)?(?(1)a|b)+$" nil nil nil nil "ab" nil nil nil) (910 "\"abc:\" =~ /^(?(?=abc)\\w{3}:|\\d\\d)$/" "^(?(?=abc)\\w{3}:|\\d\\d)$" nil nil nil nil "abc:" nil "abc:" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (911 "\"12\" =~ /^(?(?=abc)\\w{3}:|\\d\\d)$/" "^(?(?=abc)\\w{3}:|\\d\\d)$" nil nil nil nil "12" nil "12" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (912 "\"123\" =~ /^(?(?=abc)\\w{3}:|\\d\\d)$/" "^(?(?=abc)\\w{3}:|\\d\\d)$" nil nil nil nil "123" nil nil nil) (913 "\"xyz\" =~ /^(?(?=abc)\\w{3}:|\\d\\d)$/" "^(?(?=abc)\\w{3}:|\\d\\d)$" nil nil nil nil "xyz" nil nil nil) (914 "\"abc:\" =~ /^(?(?!abc)\\d\\d|\\w{3}:)$/" "^(?(?!abc)\\d\\d|\\w{3}:)$" nil nil nil nil "abc:" nil "abc:" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (915 "\"12\" =~ /^(?(?!abc)\\d\\d|\\w{3}:)$/" "^(?(?!abc)\\d\\d|\\w{3}:)$" nil nil nil nil "12" nil "12" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (916 "\"123\" =~ /^(?(?!abc)\\d\\d|\\w{3}:)$/" "^(?(?!abc)\\d\\d|\\w{3}:)$" nil nil nil nil "123" nil nil nil) (917 "\"xyz\" =~ /^(?(?!abc)\\d\\d|\\w{3}:)$/" "^(?(?!abc)\\d\\d|\\w{3}:)$" nil nil nil nil "xyz" nil nil nil) (918 "\"foobar\" =~ /(?(?<=foo)bar|cat)/" "(?(?<=foo)bar|cat)" nil nil nil nil "foobar" nil "bar" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (919 "\"cat\" =~ /(?(?<=foo)bar|cat)/" "(?(?<=foo)bar|cat)" nil nil nil nil "cat" nil "cat" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (920 "\"fcat\" =~ /(?(?<=foo)bar|cat)/" "(?(?<=foo)bar|cat)" nil nil nil nil "fcat" nil "cat" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (921 "\"focat\" =~ /(?(?<=foo)bar|cat)/" "(?(?<=foo)bar|cat)" nil nil nil nil "focat" nil "cat" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (922 "\"foocat\" =~ /(?(?<=foo)bar|cat)/" "(?(?<=foo)bar|cat)" nil nil nil nil "foocat" nil nil nil) (923 "\"foobar\" =~ /(?(?a*)*/" "(?>a*)*" nil nil nil nil "a" nil "a" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (955 "\"aa\" =~ /(?>a*)*/" "(?>a*)*" nil nil nil nil "aa" nil "aa" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (956 "\"aaaa\" =~ /(?>a*)*/" "(?>a*)*" nil nil nil nil "aaaa" nil "aaaa" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (957 "\"abc\" =~ /(abc|)+/" "(abc|)+" nil nil nil nil "abc" nil "abc" ("" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (958 "\"abcabc\" =~ /(abc|)+/" "(abc|)+" nil nil nil nil "abcabc" nil "abcabc" ("" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (959 "\"abcabcabc\" =~ /(abc|)+/" "(abc|)+" nil nil nil nil "abcabcabc" nil "abcabcabc" ("" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (960 "\"xyz\" =~ /(abc|)+/" "(abc|)+" nil nil nil nil "xyz" nil "" ("" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (961 "\"a\" =~ /([a]*)*/" "([a]*)*" nil nil nil nil "a" nil "a" ("" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (962 "\"aaaaa\" =~ /([a]*)*/" "([a]*)*" nil nil nil nil "aaaaa" nil "aaaaa" ("" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (963 "\"a\" =~ /([ab]*)*/" "([ab]*)*" nil nil nil nil "a" nil "a" ("" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (964 "\"b\" =~ /([ab]*)*/" "([ab]*)*" nil nil nil nil "b" nil "b" ("" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (965 "\"ababab\" =~ /([ab]*)*/" "([ab]*)*" nil nil nil nil "ababab" nil "ababab" ("" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (966 "\"aaaabcde\" =~ /([ab]*)*/" "([ab]*)*" nil nil nil nil "aaaabcde" nil "aaaab" ("" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (967 "\"bbbb\" =~ /([ab]*)*/" "([ab]*)*" nil nil nil nil "bbbb" nil "bbbb" ("" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (968 "\"b\" =~ /([^a]*)*/" "([^a]*)*" nil nil nil nil "b" nil "b" ("" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (969 "\"bbbb\" =~ /([^a]*)*/" "([^a]*)*" nil nil nil nil "bbbb" nil "bbbb" ("" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (970 "\"aaa\" =~ /([^a]*)*/" "([^a]*)*" nil nil nil nil "aaa" nil "" ("" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (971 "\"cccc\" =~ /([^ab]*)*/" "([^ab]*)*" nil nil nil nil "cccc" nil "cccc" ("" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (972 "\"abab\" =~ /([^ab]*)*/" "([^ab]*)*" nil nil nil nil "abab" nil "" ("" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (973 "\"a\" =~ /([a]*?)*/" "([a]*?)*" nil nil nil nil "a" nil "" ("" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (974 "\"aaaa\" =~ /([a]*?)*/" "([a]*?)*" nil nil nil nil "aaaa" nil "" ("" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (975 "\"a\" =~ /([ab]*?)*/" "([ab]*?)*" nil nil nil nil "a" nil "" ("" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (976 "\"b\" =~ /([ab]*?)*/" "([ab]*?)*" nil nil nil nil "b" nil "" ("" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (977 "\"abab\" =~ /([ab]*?)*/" "([ab]*?)*" nil nil nil nil "abab" nil "" ("" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (978 "\"baba\" =~ /([ab]*?)*/" "([ab]*?)*" nil nil nil nil "baba" nil "" ("" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (979 "\"b\" =~ /([^a]*?)*/" "([^a]*?)*" nil nil nil nil "b" nil "" ("" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (980 "\"bbbb\" =~ /([^a]*?)*/" "([^a]*?)*" nil nil nil nil "bbbb" nil "" ("" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (981 "\"aaa\" =~ /([^a]*?)*/" "([^a]*?)*" nil nil nil nil "aaa" nil "" ("" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (982 "\"c\" =~ /([^ab]*?)*/" "([^ab]*?)*" nil nil nil nil "c" nil "" ("" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (983 "\"cccc\" =~ /([^ab]*?)*/" "([^ab]*?)*" nil nil nil nil "cccc" nil "" ("" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (984 "\"baba\" =~ /([^ab]*?)*/" "([^ab]*?)*" nil nil nil nil "baba" nil "" ("" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (985 "\"a\" =~ /(?>a*)*/" "(?>a*)*" nil nil nil nil "a" nil "a" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (986 "\"aaabcde\" =~ /(?>a*)*/" "(?>a*)*" nil nil nil nil "aaabcde" nil "aaa" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (987 "\"aaaaa\" =~ /((?>a*))*/" "((?>a*))*" nil nil nil nil "aaaaa" nil "aaaaa" ("" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (988 "\"aabbaa\" =~ /((?>a*))*/" "((?>a*))*" nil nil nil nil "aabbaa" nil "aa" ("" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (989 "\"aaaaa\" =~ /((?>a*?))*/" "((?>a*?))*" nil nil nil nil "aaaaa" nil "" ("" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (990 "\"aabbaa\" =~ /((?>a*?))*/" "((?>a*?))*" nil nil nil nil "aabbaa" nil "" ("" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (991 "\"12-sep-98\" =~ /(?(?=[^a-z]+[a-z]) \\d{2}-[a-z]{3}-\\d{2} | \\d{2}-\\d{2}-\\d{2} ) /x" "(?(?=[^a-z]+[a-z]) \\d{2}-[a-z]{3}-\\d{2} | \\d{2}-\\d{2}-\\d{2} ) " nil nil nil t "12-sep-98" nil "12-sep-98" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (992 "\"12-09-98\" =~ /(?(?=[^a-z]+[a-z]) \\d{2}-[a-z]{3}-\\d{2} | \\d{2}-\\d{2}-\\d{2} ) /x" "(?(?=[^a-z]+[a-z]) \\d{2}-[a-z]{3}-\\d{2} | \\d{2}-\\d{2}-\\d{2} ) " nil nil nil t "12-09-98" nil "12-09-98" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (993 "\"sep-12-98\" =~ /(?(?=[^a-z]+[a-z]) \\d{2}-[a-z]{3}-\\d{2} | \\d{2}-\\d{2}-\\d{2} ) /x" "(?(?=[^a-z]+[a-z]) \\d{2}-[a-z]{3}-\\d{2} | \\d{2}-\\d{2}-\\d{2} ) " nil nil nil t "sep-12-98" nil nil nil) (994 "\"foobarfoo\" =~ /(?<=(foo))bar\\1/" "(?<=(foo))bar\\1" nil nil nil nil "foobarfoo" nil "barfoo" ("foo" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (995 "\"foobarfootling\" =~ /(?<=(foo))bar\\1/" "(?<=(foo))bar\\1" nil nil nil nil "foobarfootling" nil "barfoo" ("foo" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (996 "\"foobar\" =~ /(?<=(foo))bar\\1/" "(?<=(foo))bar\\1" nil nil nil nil "foobar" nil nil nil) (997 "\"barfoo\" =~ /(?<=(foo))bar\\1/" "(?<=(foo))bar\\1" nil nil nil nil "barfoo" nil nil nil) (998 "\"saturday\" =~ /(?i:saturday|sunday)/" "(?i:saturday|sunday)" nil nil nil nil "saturday" nil "saturday" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (999 "\"sunday\" =~ /(?i:saturday|sunday)/" "(?i:saturday|sunday)" nil nil nil nil "sunday" nil "sunday" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (1000 "\"Saturday\" =~ /(?i:saturday|sunday)/" "(?i:saturday|sunday)" nil nil nil nil "Saturday" nil "Saturday" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (1001 "\"Sunday\" =~ /(?i:saturday|sunday)/" "(?i:saturday|sunday)" nil nil nil nil "Sunday" nil "Sunday" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (1002 "\"SATURDAY\" =~ /(?i:saturday|sunday)/" "(?i:saturday|sunday)" nil nil nil nil "SATURDAY" nil "SATURDAY" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (1003 "\"SUNDAY\" =~ /(?i:saturday|sunday)/" "(?i:saturday|sunday)" nil nil nil nil "SUNDAY" nil "SUNDAY" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (1004 "\"SunDay\" =~ /(?i:saturday|sunday)/" "(?i:saturday|sunday)" nil nil nil nil "SunDay" nil "SunDay" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (1005 "\"abcx\" =~ /(a(?i)bc|BB)x/" "(a(?i)bc|BB)x" nil nil nil nil "abcx" nil "abcx" ("abc" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (1006 "\"aBCx\" =~ /(a(?i)bc|BB)x/" "(a(?i)bc|BB)x" nil nil nil nil "aBCx" nil "aBCx" ("aBC" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (1007 "\"bbx\" =~ /(a(?i)bc|BB)x/" "(a(?i)bc|BB)x" nil nil nil nil "bbx" nil "bbx" ("bb" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (1008 "\"BBx\" =~ /(a(?i)bc|BB)x/" "(a(?i)bc|BB)x" nil nil nil nil "BBx" nil "BBx" ("BB" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (1009 "\"abcX\" =~ /(a(?i)bc|BB)x/" "(a(?i)bc|BB)x" nil nil nil nil "abcX" nil nil nil) (1010 "\"aBCX\" =~ /(a(?i)bc|BB)x/" "(a(?i)bc|BB)x" nil nil nil nil "aBCX" nil nil nil) (1011 "\"bbX\" =~ /(a(?i)bc|BB)x/" "(a(?i)bc|BB)x" nil nil nil nil "bbX" nil nil nil) (1012 "\"BBX\" =~ /(a(?i)bc|BB)x/" "(a(?i)bc|BB)x" nil nil nil nil "BBX" nil nil nil) (1013 "\"ac\" =~ /^([ab](?i)[cd]|[ef])/" "^([ab](?i)[cd]|[ef])" nil nil nil nil "ac" nil "ac" ("ac" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (1014 "\"aC\" =~ /^([ab](?i)[cd]|[ef])/" "^([ab](?i)[cd]|[ef])" nil nil nil nil "aC" nil "aC" ("aC" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (1015 "\"bD\" =~ /^([ab](?i)[cd]|[ef])/" "^([ab](?i)[cd]|[ef])" nil nil nil nil "bD" nil "bD" ("bD" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (1016 "\"elephant\" =~ /^([ab](?i)[cd]|[ef])/" "^([ab](?i)[cd]|[ef])" nil nil nil nil "elephant" nil "e" ("e" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (1017 "\"Europe\" =~ /^([ab](?i)[cd]|[ef])/" "^([ab](?i)[cd]|[ef])" nil nil nil nil "Europe" nil "E" ("E" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (1018 "\"frog\" =~ /^([ab](?i)[cd]|[ef])/" "^([ab](?i)[cd]|[ef])" nil nil nil nil "frog" nil "f" ("f" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (1019 "\"France\" =~ /^([ab](?i)[cd]|[ef])/" "^([ab](?i)[cd]|[ef])" nil nil nil nil "France" nil "F" ("F" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (1020 "\"Africa\" =~ /^([ab](?i)[cd]|[ef])/" "^([ab](?i)[cd]|[ef])" nil nil nil nil "Africa" nil nil nil) (1021 "\"ab\" =~ /^(ab|a(?i)[b-c](?m-i)d|x(?i)y|z)/" "^(ab|a(?i)[b-c](?m-i)d|x(?i)y|z)" nil nil nil nil "ab" nil "ab" ("ab" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (1022 "\"aBd\" =~ /^(ab|a(?i)[b-c](?m-i)d|x(?i)y|z)/" "^(ab|a(?i)[b-c](?m-i)d|x(?i)y|z)" nil nil nil nil "aBd" nil "aBd" ("aBd" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (1023 "\"xy\" =~ /^(ab|a(?i)[b-c](?m-i)d|x(?i)y|z)/" "^(ab|a(?i)[b-c](?m-i)d|x(?i)y|z)" nil nil nil nil "xy" nil "xy" ("xy" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (1024 "\"xY\" =~ /^(ab|a(?i)[b-c](?m-i)d|x(?i)y|z)/" "^(ab|a(?i)[b-c](?m-i)d|x(?i)y|z)" nil nil nil nil "xY" nil "xY" ("xY" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (1025 "\"zebra\" =~ /^(ab|a(?i)[b-c](?m-i)d|x(?i)y|z)/" "^(ab|a(?i)[b-c](?m-i)d|x(?i)y|z)" nil nil nil nil "zebra" nil "z" ("z" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (1026 "\"Zambesi\" =~ /^(ab|a(?i)[b-c](?m-i)d|x(?i)y|z)/" "^(ab|a(?i)[b-c](?m-i)d|x(?i)y|z)" nil nil nil nil "Zambesi" nil "Z" ("Z" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (1027 "\"aCD\" =~ /^(ab|a(?i)[b-c](?m-i)d|x(?i)y|z)/" "^(ab|a(?i)[b-c](?m-i)d|x(?i)y|z)" nil nil nil nil "aCD" nil nil nil) (1028 "\"XY\" =~ /^(ab|a(?i)[b-c](?m-i)d|x(?i)y|z)/" "^(ab|a(?i)[b-c](?m-i)d|x(?i)y|z)" nil nil nil nil "XY" nil nil nil) (1029 "\"foo\\nbar\" =~ /(?<=foo\\n)^bar/m" "(?<=foo\\n)^bar" nil t nil nil "foo bar" nil "bar" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (1030 "\"bar\" =~ /(?<=foo\\n)^bar/m" "(?<=foo\\n)^bar" nil t nil nil "bar" nil nil nil) (1031 "\"baz\\nbar\" =~ /(?<=foo\\n)^bar/m" "(?<=foo\\n)^bar" nil t nil nil "baz bar" nil nil nil) (1032 "\"barbaz\" =~ /(?<=(?]&/" "^[<>]&" nil nil nil nil "<&OUT" nil "<&" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (1369 "\"aaaaaaaaaa\" =~ /^(a\\1?){4}$/" "^(a\\1?){4}$" nil nil nil nil "aaaaaaaaaa" nil "aaaaaaaaaa" ("aaaa" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (1370 "\"AB\" =~ /^(a\\1?){4}$/" "^(a\\1?){4}$" nil nil nil nil "AB" nil nil nil) (1371 "\"aaaaaaaaa\" =~ /^(a\\1?){4}$/" "^(a\\1?){4}$" nil nil nil nil "aaaaaaaaa" nil nil nil) (1372 "\"aaaaaaaaaaa\" =~ /^(a\\1?){4}$/" "^(a\\1?){4}$" nil nil nil nil "aaaaaaaaaaa" nil nil nil) (1373 "\"aaaaaaaaaa\" =~ /^(a(?(1)\\1)){4}$/" "^(a(?(1)\\1)){4}$" nil nil nil nil "aaaaaaaaaa" nil "aaaaaaaaaa" ("aaaa" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (1374 "\"aaaaaaaaa\" =~ /^(a(?(1)\\1)){4}$/" "^(a(?(1)\\1)){4}$" nil nil nil nil "aaaaaaaaa" nil nil nil) (1375 "\"aaaaaaaaaaa\" =~ /^(a(?(1)\\1)){4}$/" "^(a(?(1)\\1)){4}$" nil nil nil nil "aaaaaaaaaaa" nil nil nil) (1376 "\"foobar\" =~ /(?:(f)(o)(o)|(b)(a)(r))*/" "(?:(f)(o)(o)|(b)(a)(r))*" nil nil nil nil "foobar" nil "foobar" ("f" "o" "o" "b" "a" "r" nil nil nil nil nil nil nil nil nil nil)) (1377 "\"ab\" =~ /(?<=a)b/" "(?<=a)b" nil nil nil nil "ab" nil "b" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (1378 "\"cb\" =~ /(?<=a)b/" "(?<=a)b" nil nil nil nil "cb" nil nil nil) (1379 "\"b\" =~ /(?<=a)b/" "(?<=a)b" nil nil nil nil "b" nil nil nil) (1380 "\"ab\" =~ /(?a+)b/" "(?>a+)b" nil nil nil nil "aaab" nil "aaab" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (1491 "\"a:[b]:\" =~ /([[:]+)/" "([[:]+)" nil nil nil nil "a:[b]:" nil ":[" (":[" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (1492 "\"a=[b]=\" =~ /([[=]+)/" "([[=]+)" nil nil nil nil "a=[b]=" nil "=[" ("=[" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (1493 "\"a.[b].\" =~ /([[.]+)/" "([[.]+)" nil nil nil nil "a.[b]." nil ".[" (".[" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (1494 "\"aaab\" =~ /((?>a+)b)/" "((?>a+)b)" nil nil nil nil "aaab" nil "aaab" ("aaab" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (1495 "\"aaab\" =~ /(?>(a+))b/" "(?>(a+))b" nil nil nil nil "aaab" nil "aaab" ("aaa" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (1496 "\"((abc(ade)ufh()()x\" =~ /((?>[^()]+)|\\([^()]*\\))+/" "((?>[^()]+)|\\([^()]*\\))+" nil nil nil nil "((abc(ade)ufh()()x" nil "abc(ade)ufh()()x" ("x" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (1497 "\"aaab\" =~ /a\\Z/" "a\\Z" nil nil nil nil "aaab" nil nil nil) (1498 "\"a\\nb\\n\" =~ /a\\Z/" "a\\Z" nil nil nil nil "a b " nil nil nil) (1499 "\"a\\nb\\n\" =~ /b\\Z/" "b\\Z" nil nil nil nil "a b " nil "b" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (1500 "\"a\\nb\" =~ /b\\Z/" "b\\Z" nil nil nil nil "a b" nil "b" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (1501 "\"a\\nb\" =~ /b\\z/" "b\\z" nil nil nil nil "a b" nil "b" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (1502 "\"a\" =~ /^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$/" "^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$" nil nil nil nil "a" nil "a" ("" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (1503 "\"abc\" =~ /^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$/" "^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$" nil nil nil nil "abc" nil "abc" ("" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (1504 "\"a-b\" =~ /^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$/" "^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$" nil nil nil nil "a-b" nil "a-b" ("" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (1505 "\"0-9\" =~ /^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$/" "^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$" nil nil nil nil "0-9" nil "0-9" ("" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (1506 "\"a.b\" =~ /^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$/" "^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$" nil nil nil nil "a.b" nil "a.b" ("" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (1507 "\"5.6.7\" =~ /^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$/" "^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$" nil nil nil nil "5.6.7" nil "5.6.7" ("" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (1508 "\"the.quick.brown.fox\" =~ /^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$/" "^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$" nil nil nil nil "the.quick.brown.fox" nil "the.quick.brown.fox" ("" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (1509 "\"a100.b200.300c\" =~ /^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$/" "^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$" nil nil nil nil "a100.b200.300c" nil "a100.b200.300c" ("" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (1510 "\"12-ab.1245\" =~ /^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$/" "^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$" nil nil nil nil "12-ab.1245" nil "12-ab.1245" ("" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (1511 "\"\\\" =~ /^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$/" "^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$" nil nil nil nil "" nil nil nil) (1512 "\".a\" =~ /^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$/" "^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$" nil nil nil nil ".a" nil nil nil) (1513 "\"-a\" =~ /^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$/" "^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$" nil nil nil nil "-a" nil nil nil) (1514 "\"a-\" =~ /^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$/" "^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$" nil nil nil nil "a-" nil nil nil) (1515 "\"a.\" =~ /^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$/" "^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$" nil nil nil nil "a." nil nil nil) (1516 "\"a_b\" =~ /^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$/" "^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$" nil nil nil nil "a_b" nil nil nil) (1517 "\"a.-\" =~ /^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$/" "^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$" nil nil nil nil "a.-" nil nil nil) (1518 "\"a..\" =~ /^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$/" "^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$" nil nil nil nil "a.." nil nil nil) (1519 "\"ab..bc\" =~ /^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$/" "^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$" nil nil nil nil "ab..bc" nil nil nil) (1520 "\"the.quick.brown.fox-\" =~ /^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$/" "^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$" nil nil nil nil "the.quick.brown.fox-" nil nil nil) (1521 "\"the.quick.brown.fox.\" =~ /^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$/" "^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$" nil nil nil nil "the.quick.brown.fox." nil nil nil) (1522 "\"the.quick.brown.fox_\" =~ /^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$/" "^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$" nil nil nil nil "the.quick.brown.fox_" nil nil nil) (1523 "\"the.quick.brown.fox+\" =~ /^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$/" "^(?>(?(1)\\.|())[^\\W_](?>[a-z0-9-]*[^\\W_])?)+$" nil nil nil nil "the.quick.brown.fox+" nil nil nil) (1524 "\"alphabetabcd\" =~ /(?>.*)(?<=(abcd|wxyz))/" "(?>.*)(?<=(abcd|wxyz))" nil nil nil nil "alphabetabcd" nil "alphabetabcd" ("abcd" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (1525 "\"endingwxyz\" =~ /(?>.*)(?<=(abcd|wxyz))/" "(?>.*)(?<=(abcd|wxyz))" nil nil nil nil "endingwxyz" nil "endingwxyz" ("wxyz" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (1526 "\"a rather long string that doesn't end with one of them\" =~ /(?>.*)(?<=(abcd|wxyz))/" "(?>.*)(?<=(abcd|wxyz))" nil nil nil nil "a rather long string that doesn't end with one of them" nil nil nil) (1527 "\"word cat dog elephant mussel cow horse canary baboon snake shark otherword\" =~ /word (?>(?:(?!otherword)[a-zA-Z0-9]+ ){0,30})otherword/" "word (?>(?:(?!otherword)[a-zA-Z0-9]+ ){0,30})otherword" nil nil nil nil "word cat dog elephant mussel cow horse canary baboon snake shark otherword" nil "word cat dog elephant mussel cow horse canary baboon snake shark otherword" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (1528 "\"word cat dog elephant mussel cow horse canary baboon snake shark\" =~ /word (?>(?:(?!otherword)[a-zA-Z0-9]+ ){0,30})otherword/" "word (?>(?:(?!otherword)[a-zA-Z0-9]+ ){0,30})otherword" nil nil nil nil "word cat dog elephant mussel cow horse canary baboon snake shark" nil nil nil) (1529 "\"word cat dog elephant mussel cow horse canary baboon snake shark the quick brown fox and the lazy dog and several other words getting close to thirty by now I hope\" =~ /word (?>[a-zA-Z0-9]+ ){0,30}otherword/" "word (?>[a-zA-Z0-9]+ ){0,30}otherword" nil nil nil nil "word cat dog elephant mussel cow horse canary baboon snake shark the quick brown fox and the lazy dog and several other words getting close to thirty by now I hope" nil nil nil) (1530 "\"999foo\" =~ /(?<=\\d{3}(?!999))foo/" "(?<=\\d{3}(?!999))foo" nil nil nil nil "999foo" nil "foo" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (1531 "\"123999foo\" =~ /(?<=\\d{3}(?!999))foo/" "(?<=\\d{3}(?!999))foo" nil nil nil nil "123999foo" nil "foo" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (1532 "\"123abcfoo\" =~ /(?<=\\d{3}(?!999))foo/" "(?<=\\d{3}(?!999))foo" nil nil nil nil "123abcfoo" nil nil nil) (1533 "\"999foo\" =~ /(?<=(?!...999)\\d{3})foo/" "(?<=(?!...999)\\d{3})foo" nil nil nil nil "999foo" nil "foo" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (1534 "\"123999foo\" =~ /(?<=(?!...999)\\d{3})foo/" "(?<=(?!...999)\\d{3})foo" nil nil nil nil "123999foo" nil "foo" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (1535 "\"123abcfoo\" =~ /(?<=(?!...999)\\d{3})foo/" "(?<=(?!...999)\\d{3})foo" nil nil nil nil "123abcfoo" nil nil nil) (1536 "\"123abcfoo\" =~ /(?<=\\d{3}(?!999)...)foo/" "(?<=\\d{3}(?!999)...)foo" nil nil nil nil "123abcfoo" nil "foo" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (1537 "\"123456foo\" =~ /(?<=\\d{3}(?!999)...)foo/" "(?<=\\d{3}(?!999)...)foo" nil nil nil nil "123456foo" nil "foo" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (1538 "\"123999foo\" =~ /(?<=\\d{3}(?!999)...)foo/" "(?<=\\d{3}(?!999)...)foo" nil nil nil nil "123999foo" nil nil nil) (1539 "\"123abcfoo\" =~ /(?<=\\d{3}...)(?\\s*)=(?>\\s*) # find
\\s*)=(?>\\s*) # find \\s*)=(?>\\s*) # find \\s*)=(?>\\s*) # find \\s*)=(?>\\s*) # find \\s*)=(?>\\s*) # find Z)+|A)*/" "((?>Z)+|A)*" nil nil nil nil "ZABCDEFG" nil "ZA" ("A" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (1555 "\"ZABCDEFG\" =~ /((?>)+|A)*/" "((?>)+|A)*" nil nil nil nil "ZABCDEFG" nil "" ("" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (1556 "\"abbab\" =~ /a*/" "a*" nil nil nil nil "abbab" nil "a" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (1557 "\"abcde\" =~ /^[a-\\d]/" "^[a-\\d]" nil nil nil nil "abcde" nil "a" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (1558 "\"-things\" =~ /^[a-\\d]/" "^[a-\\d]" nil nil nil nil "-things" nil "-" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (1559 "\"0digit\" =~ /^[a-\\d]/" "^[a-\\d]" nil nil nil nil "0digit" nil "0" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (1560 "\"bcdef\" =~ /^[a-\\d]/" "^[a-\\d]" nil nil nil nil "bcdef" nil nil nil) (1561 "\"abcde\" =~ /^[\\d-a]/" "^[\\d-a]" nil nil nil nil "abcde" nil "a" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (1562 "\"-things\" =~ /^[\\d-a]/" "^[\\d-a]" nil nil nil nil "-things" nil "-" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (1563 "\"0digit\" =~ /^[\\d-a]/" "^[\\d-a]" nil nil nil nil "0digit" nil "0" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (1564 "\"bcdef\" =~ /^[\\d-a]/" "^[\\d-a]" nil nil nil nil "bcdef" nil nil nil) (1565 "\"abcdef\" =~ /(?<=abc).*(?=def)/" "(?<=abc).*(?=def)" nil nil nil nil "abcdef" nil "" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (1566 "\"abcxdef\" =~ /(?<=abc).*(?=def)/" "(?<=abc).*(?=def)" nil nil nil nil "abcxdef" nil "x" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (1567 "\"abcxdefxdef\" =~ /(?<=abc).*(?=def)/" "(?<=abc).*(?=def)" nil nil nil nil "abcxdefxdef" nil "xdefx" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (1568 "\"abcdef\" =~ /(?<=abc).*?(?=def)/" "(?<=abc).*?(?=def)" nil nil nil nil "abcdef" nil "" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (1569 "\"abcxdef\" =~ /(?<=abc).*?(?=def)/" "(?<=abc).*?(?=def)" nil nil nil nil "abcxdef" nil "x" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (1570 "\"abcxdefxdef\" =~ /(?<=abc).*?(?=def)/" "(?<=abc).*?(?=def)" nil nil nil nil "abcxdefxdef" nil "x" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (1571 "\"abcdef\" =~ /(?<=abc).+(?=def)/" "(?<=abc).+(?=def)" nil nil nil nil "abcdef" nil nil nil) (1572 "\"abcxdef\" =~ /(?<=abc).+(?=def)/" "(?<=abc).+(?=def)" nil nil nil nil "abcxdef" nil "x" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (1573 "\"abcxdefxdef\" =~ /(?<=abc).+(?=def)/" "(?<=abc).+(?=def)" nil nil nil nil "abcxdefxdef" nil "xdefx" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (1574 "\"abcdef\" =~ /(?<=abc).+?(?=def)/" "(?<=abc).+?(?=def)" nil nil nil nil "abcdef" nil nil nil) (1575 "\"abcxdef\" =~ /(?<=abc).+?(?=def)/" "(?<=abc).+?(?=def)" nil nil nil nil "abcxdef" nil "x" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (1576 "\"abcxdefxdef\" =~ /(?<=abc).+?(?=def)/" "(?<=abc).+?(?=def)" nil nil nil nil "abcxdefxdef" nil "x" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (1577 "\"-abcdef\" =~ /(?<=\\b)(.*)/" "(?<=\\b)(.*)" nil nil nil nil "-abcdef" nil "abcdef" ("abcdef" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (1578 "\"abcdef\" =~ /(?<=\\b)(.*)/" "(?<=\\b)(.*)" nil nil nil nil "abcdef" nil "abcdef" ("abcdef" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (1579 "\"-abcdef\" =~ /(?<=\\B)(.*)/" "(?<=\\B)(.*)" nil nil nil nil "-abcdef" nil "-abcdef" ("-abcdef" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (1580 "\"abcdef\" =~ /(?<=\\B)(.*)/" "(?<=\\B)(.*)" nil nil nil nil "abcdef" nil "bcdef" ("bcdef" nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (1581 "\"'a'\" =~ /^'[ab]'/" "^'[ab]'" nil nil nil nil "'a'" nil "'a'" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (1582 "\"'b'\" =~ /^'[ab]'/" "^'[ab]'" nil nil nil nil "'b'" nil "'b'" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (1583 "\"x'a'\" =~ /^'[ab]'/" "^'[ab]'" nil nil nil nil "x'a'" nil nil nil) (1584 "\"'a'x\" =~ /^'[ab]'/" "^'[ab]'" nil nil nil nil "'a'x" nil "'a'" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (1585 "\"'ab'\" =~ /^'[ab]'/" "^'[ab]'" nil nil nil nil "'ab'" nil nil nil) (1586 "\"'a'\" =~ /^'[ab]'$/" "^'[ab]'$" nil nil nil nil "'a'" nil "'a'" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (1587 "\"'b'\" =~ /^'[ab]'$/" "^'[ab]'$" nil nil nil nil "'b'" nil "'b'" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (1588 "\"x'a'\" =~ /^'[ab]'$/" "^'[ab]'$" nil nil nil nil "x'a'" nil nil nil) (1589 "\"'a'x\" =~ /^'[ab]'$/" "^'[ab]'$" nil nil nil nil "'a'x" nil nil nil) (1590 "\"'ab'\" =~ /^'[ab]'$/" "^'[ab]'$" nil nil nil nil "'ab'" nil nil nil) (1591 "\"'a'\" =~ /'[ab]'$/" "'[ab]'$" nil nil nil nil "'a'" nil "'a'" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (1592 "\"'b'\" =~ /'[ab]'$/" "'[ab]'$" nil nil nil nil "'b'" nil "'b'" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (1593 "\"x'a'\" =~ /'[ab]'$/" "'[ab]'$" nil nil nil nil "x'a'" nil "'a'" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (1594 "\"'a'x\" =~ /'[ab]'$/" "'[ab]'$" nil nil nil nil "'a'x" nil nil nil) (1595 "\"'ab'\" =~ /'[ab]'$/" "'[ab]'$" nil nil nil nil "'ab'" nil nil nil) (1596 "\"'a'\" =~ /'[ab]'/" "'[ab]'" nil nil nil nil "'a'" nil "'a'" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (1597 "\"'b'\" =~ /'[ab]'/" "'[ab]'" nil nil nil nil "'b'" nil "'b'" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (1598 "\"x'a'\" =~ /'[ab]'/" "'[ab]'" nil nil nil nil "x'a'" nil "'a'" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (1599 "\"'a'x\" =~ /'[ab]'/" "'[ab]'" nil nil nil nil "'a'x" nil "'a'" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (1600 "\"'ab'\" =~ /'[ab]'/" "'[ab]'" nil nil nil nil "'ab'" nil nil nil) (1601 "\"abc\" =~ /abc\\E/" "abc\\E" nil nil nil nil "abc" nil "abc" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (1602 "\"abcE\" =~ /abc\\E/" "abc\\E" nil nil nil nil "abcE" nil "abc" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (1603 "\"abcx\" =~ /abc[\\Ex]/" "abc[\\Ex]" nil nil nil nil "abcx" nil "abcx" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (1604 "\"abcE\" =~ /abc[\\Ex]/" "abc[\\Ex]" nil nil nil nil "abcE" nil nil nil) (1605 "\"a*\" =~ /^\\Qa*\\E$/" "^\\Qa*\\E$" nil nil nil nil "a*" nil "a*" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (1606 "\"a\" =~ /^\\Qa*\\E$/" "^\\Qa*\\E$" nil nil nil nil "a" nil nil nil) (1607 "\"a*x\" =~ /\\Qa*x\\E/" "\\Qa*x\\E" nil nil nil nil "a*x" nil "a*x" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (1608 "\"a*\" =~ /\\Qa*x\\E/" "\\Qa*x\\E" nil nil nil nil "a*" nil nil nil) (1609 "\"a*x\" =~ /\\Qa*x/" "\\Qa*x" nil nil nil nil "a*x" nil "a*x" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (1610 "\"a*\" =~ /\\Qa*x/" "\\Qa*x" nil nil nil nil "a*" nil nil nil) (1611 "\"a*x\" =~ /\\Q\\Qa*x\\E\\E/" "\\Q\\Qa*x\\E\\E" nil nil nil nil "a*x" nil nil nil) (1612 "\"a\\\\*x\" =~ /\\Q\\Qa*x\\E\\E/" "\\Q\\Qa*x\\E\\E" nil nil nil nil "a\\*x" nil "a\\*x" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (1613 "\"a*x\" =~ /\\Q\\Qa*x\\E/" "\\Q\\Qa*x\\E" nil nil nil nil "a*x" nil nil nil) (1614 "\"a\\\\*x\" =~ /\\Q\\Qa*x\\E/" "\\Q\\Qa*x\\E" nil nil nil nil "a\\*x" nil "a\\*x" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (1615 "\"a[x]\" =~ /a\\Q[x\\E]/" "a\\Q[x\\E]" nil nil nil nil "a[x]" nil "a[x]" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (1616 "\"ax\" =~ /a\\Q[x\\E]/" "a\\Q[x\\E]" nil nil nil nil "ax" nil nil nil) (1617 "\"a\" =~ /a#comment\\Q... {2}/x" "a#comment\\Q... {2}" nil nil nil t "a" nil nil nil) (1618 "\"aa\" =~ /a#comment\\Q... {2}/x" "a#comment\\Q... {2}" nil nil nil t "aa" nil "aa" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (1619 "\"a\" =~ /a(?#comment\\Q... ){2}/x" "a(?#comment\\Q... ){2}" nil nil nil t "a" nil nil nil) (1620 "\"aa\" =~ /a(?#comment\\Q... ){2}/x" "a(?#comment\\Q... ){2}" nil nil nil t "aa" nil "aa" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (1621 "\"a.\" =~ /(?x)a#\\Q ./" "(?x)a#\\Q ." nil nil nil nil "a." nil "a." (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (1622 "\"aa\" =~ /(?x)a#\\Q ./" "(?x)a#\\Q ." nil nil nil nil "aa" nil nil nil) (1623 "\"abcdxklqj\" =~ /ab(?=.*q)cd/" "ab(?=.*q)cd" nil nil nil nil "abcdxklqj" nil "abcd" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) (1624 "\"ab\" =~ /a(?!.*$)b/" "a(?!.*$)b" nil nil nil nil "ab" nil nil nil) (1625 "\"Axi\" =~ /.{2}[a-z]/" ".{2}[a-z]" nil nil nil nil "Axi" nil "Axi" (nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil nil)) cl-ppcre-2.0.3/test/perltestinput0000644000175700010010000021342711041362031015263 0ustar ediNone/the quick brown fox/ the quick brown fox The quick brown FOX What do you know about the quick brown fox? What do you know about THE QUICK BROWN FOX? /The quick brown fox/i the quick brown fox The quick brown FOX What do you know about the quick brown fox? What do you know about THE QUICK BROWN FOX? /abcd\t\n\r\f\a\e\071\x3b\$\\\?caxyz/ abcd\t\n\r\f\a\e9;\$\\?caxyz /a*abc?xyz+pqr{3}ab{2,}xy{4,5}pq{0,6}AB{0,}zz/ abxyzpqrrrabbxyyyypqAzz abxyzpqrrrabbxyyyypqAzz aabxyzpqrrrabbxyyyypqAzz aaabxyzpqrrrabbxyyyypqAzz aaaabxyzpqrrrabbxyyyypqAzz abcxyzpqrrrabbxyyyypqAzz aabcxyzpqrrrabbxyyyypqAzz aaabcxyzpqrrrabbxyyyypAzz aaabcxyzpqrrrabbxyyyypqAzz aaabcxyzpqrrrabbxyyyypqqAzz aaabcxyzpqrrrabbxyyyypqqqAzz aaabcxyzpqrrrabbxyyyypqqqqAzz aaabcxyzpqrrrabbxyyyypqqqqqAzz aaabcxyzpqrrrabbxyyyypqqqqqqAzz aaaabcxyzpqrrrabbxyyyypqAzz abxyzzpqrrrabbxyyyypqAzz aabxyzzzpqrrrabbxyyyypqAzz aaabxyzzzzpqrrrabbxyyyypqAzz aaaabxyzzzzpqrrrabbxyyyypqAzz abcxyzzpqrrrabbxyyyypqAzz aabcxyzzzpqrrrabbxyyyypqAzz aaabcxyzzzzpqrrrabbxyyyypqAzz aaaabcxyzzzzpqrrrabbxyyyypqAzz aaaabcxyzzzzpqrrrabbbxyyyypqAzz aaaabcxyzzzzpqrrrabbbxyyyyypqAzz aaabcxyzpqrrrabbxyyyypABzz aaabcxyzpqrrrabbxyyyypABBzz >>>aaabxyzpqrrrabbxyyyypqAzz >aaaabxyzpqrrrabbxyyyypqAzz >>>>abcxyzpqrrrabbxyyyypqAzz abxyzpqrrabbxyyyypqAzz abxyzpqrrrrabbxyyyypqAzz abxyzpqrrrabxyyyypqAzz aaaabcxyzzzzpqrrrabbbxyyyyyypqAzz aaaabcxyzzzzpqrrrabbbxyyypqAzz aaabcxyzpqrrrabbxyyyypqqqqqqqAzz /^(abc){1,2}zz/ abczz abcabczz zz abcabcabczz >>abczz /^(b+?|a){1,2}?c/ bc bbc bbbc bac bbac aac abbbbbbbbbbbc bbbbbbbbbbbac aaac abbbbbbbbbbbac /^(b+|a){1,2}c/ bc bbc bbbc bac bbac aac abbbbbbbbbbbc bbbbbbbbbbbac aaac abbbbbbbbbbbac /^(b+|a){1,2}?bc/ bbc /^(b*|ba){1,2}?bc/ babc bbabc bababc bababbc babababc /^(ba|b*){1,2}?bc/ babc bbabc bababc bababbc babababc /^\ca\cA\c[\c{\c:/ \x01\x01\e;z /^[ab\]cde]/ athing bthing ]thing cthing dthing ething fthing [thing \\thing /^[]cde]/ ]thing cthing dthing ething athing fthing /^[^ab\]cde]/ fthing [thing \\thing athing bthing ]thing cthing dthing ething /^[^]cde]/ athing fthing ]thing cthing dthing ething /^\/ /^ÿ/ ÿ /^[0-9]+$/ 0 1 2 3 4 5 6 7 8 9 10 100 abc /^.*nter/ enter inter uponter /^xxx[0-9]+$/ xxx0 xxx1234 xxx /^.+[0-9][0-9][0-9]$/ x123 xx123 123456 123 x1234 /^.+?[0-9][0-9][0-9]$/ x123 xx123 123456 123 x1234 /^([^!]+)!(.+)=apquxz\.ixr\.zzz\.ac\.uk$/ abc!pqr=apquxz.ixr.zzz.ac.uk !pqr=apquxz.ixr.zzz.ac.uk abc!=apquxz.ixr.zzz.ac.uk abc!pqr=apquxz:ixr.zzz.ac.uk abc!pqr=apquxz.ixr.zzz.ac.ukk /:/ Well, we need a colon: somewhere Fail if we don't /([\da-f:]+)$/i 0abc abc fed E :: 5f03:12C0::932e fed def Any old stuff 0zzz gzzz fed\x20 Any old rubbish /^.*\.(\d{1,3})\.(\d{1,3})\.(\d{1,3})$/ .1.2.3 A.12.123.0 .1.2.3333 1.2.3 1234.2.3 /^(\d+)\s+IN\s+SOA\s+(\S+)\s+(\S+)\s*\(\s*$/ 1 IN SOA non-sp1 non-sp2( 1 IN SOA non-sp1 non-sp2 ( 1IN SOA non-sp1 non-sp2( /^[a-zA-Z\d][a-zA-Z\d\-]*(\.[a-zA-Z\d][a-zA-z\d\-]*)*\.$/ a. Z. 2. ab-c.pq-r. sxk.zzz.ac.uk. x-.y-. -abc.peq. /^\*\.[a-z]([a-z\-\d]*[a-z\d]+)?(\.[a-z]([a-z\-\d]*[a-z\d]+)?)*$/ *.a *.b0-a *.c3-b.c *.c-a.b-c *.0 *.a- *.a-b.c- *.c-a.0-c /^(?=ab(de))(abd)(e)/ abde /^(?!(ab)de|x)(abd)(f)/ abdf /^(?=(ab(cd)))(ab)/ abcd /^[\da-f](\.[\da-f])*$/i a.b.c.d A.B.C.D a.b.c.1.2.3.C /^\".*\"\s*(;.*)?$/ \"1234\" \"abcd\" ; \"\" ; rhubarb \"1234\" : things /^$/ \ / ^ a (?# begins with a) b\sc (?# then b c) $ (?# then end)/x ab c abc ab cde /(?x) ^ a (?# begins with a) b\sc (?# then b c) $ (?# then end)/ ab c abc ab cde /^ a\ b[c ]d $/x a bcd a b d abcd ab d /^(a(b(c)))(d(e(f)))(h(i(j)))(k(l(m)))$/ abcdefhijklm /^(?:a(b(c)))(?:d(e(f)))(?:h(i(j)))(?:k(l(m)))$/ abcdefhijklm /^[\w][\W][\s][\S][\d][\D][\b][\n][\c]][\022]/ a+ Z0+\x08\n\x1d\x12 /^[.^$|()*+?{,}]+/ .^\$(*+)|{?,?} /^a*\w/ z az aaaz a aa aaaa a+ aa+ /^a*?\w/ z az aaaz a aa aaaa a+ aa+ /^a+\w/ az aaaz aa aaaa aa+ /^a+?\w/ az aaaz aa aaaa aa+ /^\d{8}\w{2,}/ 1234567890 12345678ab 12345678__ 1234567 /^[aeiou\d]{4,5}$/ uoie 1234 12345 aaaaa 123456 /^[aeiou\d]{4,5}?/ uoie 1234 12345 aaaaa 123456 /\A(abc|def)=(\1){2,3}\Z/ abc=abcabc def=defdefdef abc=defdef /^(a)(b)(c)(d)(e)(f)(g)(h)(i)(j)(k)\11*(\3\4)\1(?#)2$/ abcdefghijkcda2 abcdefghijkkkkcda2 /(cat(a(ract|tonic)|erpillar)) \1()2(3)/ cataract cataract23 catatonic catatonic23 caterpillar caterpillar23 /^From +([^ ]+) +[a-zA-Z][a-zA-Z][a-zA-Z] +[a-zA-Z][a-zA-Z][a-zA-Z] +[0-9]?[0-9] +[0-9][0-9]:[0-9][0-9]/ From abcd Mon Sep 01 12:33:02 1997 /^From\s+\S+\s+([a-zA-Z]{3}\s+){2}\d{1,2}\s+\d\d:\d\d/ From abcd Mon Sep 01 12:33:02 1997 From abcd Mon Sep 1 12:33:02 1997 From abcd Sep 01 12:33:02 1997 /^12.34/s 12\n34 12\r34 /\w+(?=\t)/ the quick brown\t fox /foo(?!bar)(.*)/ foobar is foolish see? /(?:(?!foo)...|^.{0,2})bar(.*)/ foobar crowbar etc barrel 2barrel A barrel /^(\D*)(?=\d)(?!123)/ abc456 abc123 /^1234(?# test newlines inside)/ 1234 /^1234 #comment in extended re /x 1234 /#rhubarb abcd/x abcd /^abcd#rhubarb/x abcd /^(a)\1{2,3}(.)/ aaab aaaab aaaaab aaaaaab /(?!^)abc/ the abc abc /(?=^)abc/ abc the abc /^[ab]{1,3}(ab*|b)/ aabbbbb /^[ab]{1,3}?(ab*|b)/ aabbbbb /^[ab]{1,3}?(ab*?|b)/ aabbbbb /^[ab]{1,3}(ab*?|b)/ aabbbbb / (?: [\040\t] | \( (?: [^\\\x80-\xff\n\015()] | \\ [^\x80-\xff] | \( (?: [^\\\x80-\xff\n\015()] | \\ [^\x80-\xff] )* \) )* \) )* # optional leading comment (?: (?: [^(\040)<>@,;:".\\\[\]\000-\037\x80-\xff]+ # some number of atom characters... (?![^(\040)<>@,;:".\\\[\]\000-\037\x80-\xff]) # ..not followed by something that could be part of an atom | " (?: # opening quote... [^\\\x80-\xff\n\015"] # Anything except backslash and quote | # or \\ [^\x80-\xff] # Escaped something (something != CR) )* " # closing quote ) # initial word (?: (?: [\040\t] | \( (?: [^\\\x80-\xff\n\015()] | \\ [^\x80-\xff] | \( (?: [^\\\x80-\xff\n\015()] | \\ [^\x80-\xff] )* \) )* \) )* \. (?: [\040\t] | \( (?: [^\\\x80-\xff\n\015()] | \\ [^\x80-\xff] | \( (?: [^\\\x80-\xff\n\015()] | \\ [^\x80-\xff] )* \) )* \) )* (?: [^(\040)<>@,;:".\\\[\]\000-\037\x80-\xff]+ # some number of atom characters... (?![^(\040)<>@,;:".\\\[\]\000-\037\x80-\xff]) # ..not followed by something that could be part of an atom | " (?: # opening quote... [^\\\x80-\xff\n\015"] # Anything except backslash and quote | # or \\ [^\x80-\xff] # Escaped something (something != CR) )* " # closing quote ) )* # further okay, if led by a period (?: [\040\t] | \( (?: [^\\\x80-\xff\n\015()] | \\ [^\x80-\xff] | \( (?: [^\\\x80-\xff\n\015()] | \\ [^\x80-\xff] )* \) )* \) )* @ (?: [\040\t] | \( (?: [^\\\x80-\xff\n\015()] | \\ [^\x80-\xff] | \( (?: [^\\\x80-\xff\n\015()] | \\ [^\x80-\xff] )* \) )* \) )* (?: [^(\040)<>@,;:".\\\[\]\000-\037\x80-\xff]+ # some number of atom characters... (?![^(\040)<>@,;:".\\\[\]\000-\037\x80-\xff]) # ..not followed by something that could be part of an atom | \[ # [ (?: [^\\\x80-\xff\n\015\[\]] | \\ [^\x80-\xff] )* # stuff \] # ] ) # initial subdomain (?: # (?: [\040\t] | \( (?: [^\\\x80-\xff\n\015()] | \\ [^\x80-\xff] | \( (?: [^\\\x80-\xff\n\015()] | \\ [^\x80-\xff] )* \) )* \) )* \. # if led by a period... (?: [\040\t] | \( (?: [^\\\x80-\xff\n\015()] | \\ [^\x80-\xff] | \( (?: [^\\\x80-\xff\n\015()] | \\ [^\x80-\xff] )* \) )* \) )* (?: [^(\040)<>@,;:".\\\[\]\000-\037\x80-\xff]+ # some number of atom characters... (?![^(\040)<>@,;:".\\\[\]\000-\037\x80-\xff]) # ..not followed by something that could be part of an atom | \[ # [ (?: [^\\\x80-\xff\n\015\[\]] | \\ [^\x80-\xff] )* # stuff \] # ] ) # ...further okay )* # address | # or (?: [^(\040)<>@,;:".\\\[\]\000-\037\x80-\xff]+ # some number of atom characters... (?![^(\040)<>@,;:".\\\[\]\000-\037\x80-\xff]) # ..not followed by something that could be part of an atom | " (?: # opening quote... [^\\\x80-\xff\n\015"] # Anything except backslash and quote | # or \\ [^\x80-\xff] # Escaped something (something != CR) )* " # closing quote ) # one word, optionally followed by.... (?: [^()<>@,;:".\\\[\]\x80-\xff\000-\010\012-\037] | # atom and space parts, or... \( (?: [^\\\x80-\xff\n\015()] | \\ [^\x80-\xff] | \( (?: [^\\\x80-\xff\n\015()] | \\ [^\x80-\xff] )* \) )* \) | # comments, or... " (?: # opening quote... [^\\\x80-\xff\n\015"] # Anything except backslash and quote | # or \\ [^\x80-\xff] # Escaped something (something != CR) )* " # closing quote # quoted strings )* < (?: [\040\t] | \( (?: [^\\\x80-\xff\n\015()] | \\ [^\x80-\xff] | \( (?: [^\\\x80-\xff\n\015()] | \\ [^\x80-\xff] )* \) )* \) )* # leading < (?: @ (?: [\040\t] | \( (?: [^\\\x80-\xff\n\015()] | \\ [^\x80-\xff] | \( (?: [^\\\x80-\xff\n\015()] | \\ [^\x80-\xff] )* \) )* \) )* (?: [^(\040)<>@,;:".\\\[\]\000-\037\x80-\xff]+ # some number of atom characters... (?![^(\040)<>@,;:".\\\[\]\000-\037\x80-\xff]) # ..not followed by something that could be part of an atom | \[ # [ (?: [^\\\x80-\xff\n\015\[\]] | \\ [^\x80-\xff] )* # stuff \] # ] ) # initial subdomain (?: # (?: [\040\t] | \( (?: [^\\\x80-\xff\n\015()] | \\ [^\x80-\xff] | \( (?: [^\\\x80-\xff\n\015()] | \\ [^\x80-\xff] )* \) )* \) )* \. # if led by a period... (?: [\040\t] | \( (?: [^\\\x80-\xff\n\015()] | \\ [^\x80-\xff] | \( (?: [^\\\x80-\xff\n\015()] | \\ [^\x80-\xff] )* \) )* \) )* (?: [^(\040)<>@,;:".\\\[\]\000-\037\x80-\xff]+ # some number of atom characters... (?![^(\040)<>@,;:".\\\[\]\000-\037\x80-\xff]) # ..not followed by something that could be part of an atom | \[ # [ (?: [^\\\x80-\xff\n\015\[\]] | \\ [^\x80-\xff] )* # stuff \] # ] ) # ...further okay )* (?: (?: [\040\t] | \( (?: [^\\\x80-\xff\n\015()] | \\ [^\x80-\xff] | \( (?: [^\\\x80-\xff\n\015()] | \\ [^\x80-\xff] )* \) )* \) )* , (?: [\040\t] | \( (?: [^\\\x80-\xff\n\015()] | \\ [^\x80-\xff] | \( (?: [^\\\x80-\xff\n\015()] | \\ [^\x80-\xff] )* \) )* \) )* @ (?: [\040\t] | \( (?: [^\\\x80-\xff\n\015()] | \\ [^\x80-\xff] | \( (?: [^\\\x80-\xff\n\015()] | \\ [^\x80-\xff] )* \) )* \) )* (?: [^(\040)<>@,;:".\\\[\]\000-\037\x80-\xff]+ # some number of atom characters... (?![^(\040)<>@,;:".\\\[\]\000-\037\x80-\xff]) # ..not followed by something that could be part of an atom | \[ # [ (?: [^\\\x80-\xff\n\015\[\]] | \\ [^\x80-\xff] )* # stuff \] # ] ) # initial subdomain (?: # (?: [\040\t] | \( (?: [^\\\x80-\xff\n\015()] | \\ [^\x80-\xff] | \( (?: [^\\\x80-\xff\n\015()] | \\ [^\x80-\xff] )* \) )* \) )* \. # if led by a period... (?: [\040\t] | \( (?: [^\\\x80-\xff\n\015()] | \\ [^\x80-\xff] | \( (?: [^\\\x80-\xff\n\015()] | \\ [^\x80-\xff] )* \) )* \) )* (?: [^(\040)<>@,;:".\\\[\]\000-\037\x80-\xff]+ # some number of atom characters... (?![^(\040)<>@,;:".\\\[\]\000-\037\x80-\xff]) # ..not followed by something that could be part of an atom | \[ # [ (?: [^\\\x80-\xff\n\015\[\]] | \\ [^\x80-\xff] )* # stuff \] # ] ) # ...further okay )* )* # further okay, if led by comma : # closing colon (?: [\040\t] | \( (?: [^\\\x80-\xff\n\015()] | \\ [^\x80-\xff] | \( (?: [^\\\x80-\xff\n\015()] | \\ [^\x80-\xff] )* \) )* \) )* )? # optional route (?: [^(\040)<>@,;:".\\\[\]\000-\037\x80-\xff]+ # some number of atom characters... (?![^(\040)<>@,;:".\\\[\]\000-\037\x80-\xff]) # ..not followed by something that could be part of an atom | " (?: # opening quote... [^\\\x80-\xff\n\015"] # Anything except backslash and quote | # or \\ [^\x80-\xff] # Escaped something (something != CR) )* " # closing quote ) # initial word (?: (?: [\040\t] | \( (?: [^\\\x80-\xff\n\015()] | \\ [^\x80-\xff] | \( (?: [^\\\x80-\xff\n\015()] | \\ [^\x80-\xff] )* \) )* \) )* \. (?: [\040\t] | \( (?: [^\\\x80-\xff\n\015()] | \\ [^\x80-\xff] | \( (?: [^\\\x80-\xff\n\015()] | \\ [^\x80-\xff] )* \) )* \) )* (?: [^(\040)<>@,;:".\\\[\]\000-\037\x80-\xff]+ # some number of atom characters... (?![^(\040)<>@,;:".\\\[\]\000-\037\x80-\xff]) # ..not followed by something that could be part of an atom | " (?: # opening quote... [^\\\x80-\xff\n\015"] # Anything except backslash and quote | # or \\ [^\x80-\xff] # Escaped something (something != CR) )* " # closing quote ) )* # further okay, if led by a period (?: [\040\t] | \( (?: [^\\\x80-\xff\n\015()] | \\ [^\x80-\xff] | \( (?: [^\\\x80-\xff\n\015()] | \\ [^\x80-\xff] )* \) )* \) )* @ (?: [\040\t] | \( (?: [^\\\x80-\xff\n\015()] | \\ [^\x80-\xff] | \( (?: [^\\\x80-\xff\n\015()] | \\ [^\x80-\xff] )* \) )* \) )* (?: [^(\040)<>@,;:".\\\[\]\000-\037\x80-\xff]+ # some number of atom characters... (?![^(\040)<>@,;:".\\\[\]\000-\037\x80-\xff]) # ..not followed by something that could be part of an atom | \[ # [ (?: [^\\\x80-\xff\n\015\[\]] | \\ [^\x80-\xff] )* # stuff \] # ] ) # initial subdomain (?: # (?: [\040\t] | \( (?: [^\\\x80-\xff\n\015()] | \\ [^\x80-\xff] | \( (?: [^\\\x80-\xff\n\015()] | \\ [^\x80-\xff] )* \) )* \) )* \. # if led by a period... (?: [\040\t] | \( (?: [^\\\x80-\xff\n\015()] | \\ [^\x80-\xff] | \( (?: [^\\\x80-\xff\n\015()] | \\ [^\x80-\xff] )* \) )* \) )* (?: [^(\040)<>@,;:".\\\[\]\000-\037\x80-\xff]+ # some number of atom characters... (?![^(\040)<>@,;:".\\\[\]\000-\037\x80-\xff]) # ..not followed by something that could be part of an atom | \[ # [ (?: [^\\\x80-\xff\n\015\[\]] | \\ [^\x80-\xff] )* # stuff \] # ] ) # ...further okay )* # address spec (?: [\040\t] | \( (?: [^\\\x80-\xff\n\015()] | \\ [^\x80-\xff] | \( (?: [^\\\x80-\xff\n\015()] | \\ [^\x80-\xff] )* \) )* \) )* > # trailing > # name and address ) (?: [\040\t] | \( (?: [^\\\x80-\xff\n\015()] | \\ [^\x80-\xff] | \( (?: [^\\\x80-\xff\n\015()] | \\ [^\x80-\xff] )* \) )* \) )* # optional trailing comment /x Alan Other user\@dom.ain \"A. Other\" (a comment) A. Other (a comment) \"/s=user/ou=host/o=place/prmd=uu.yy/admd= /c=gb/\"\@x400-re.lay A missing angle @,;:".\\\[\]\000-\037\x80-\xff]+ # some number of atom characters... (?![^(\040)<>@,;:".\\\[\]\000-\037\x80-\xff]) # ..not followed by something that could be part of an atom # Atom | # or " # " [^\\\x80-\xff\n\015"] * # normal (?: \\ [^\x80-\xff] [^\\\x80-\xff\n\015"] * )* # ( special normal* )* " # " # Quoted string ) [\040\t]* # Nab whitespace. (?: \( # ( [^\\\x80-\xff\n\015()] * # normal* (?: # ( (?: \\ [^\x80-\xff] | \( # ( [^\\\x80-\xff\n\015()] * # normal* (?: \\ [^\x80-\xff] [^\\\x80-\xff\n\015()] * )* # (special normal*)* \) # ) ) # special [^\\\x80-\xff\n\015()] * # normal* )* # )* \) # ) [\040\t]* )* # If comment found, allow more spaces. (?: \. [\040\t]* # Nab whitespace. (?: \( # ( [^\\\x80-\xff\n\015()] * # normal* (?: # ( (?: \\ [^\x80-\xff] | \( # ( [^\\\x80-\xff\n\015()] * # normal* (?: \\ [^\x80-\xff] [^\\\x80-\xff\n\015()] * )* # (special normal*)* \) # ) ) # special [^\\\x80-\xff\n\015()] * # normal* )* # )* \) # ) [\040\t]* )* # If comment found, allow more spaces. (?: [^(\040)<>@,;:".\\\[\]\000-\037\x80-\xff]+ # some number of atom characters... (?![^(\040)<>@,;:".\\\[\]\000-\037\x80-\xff]) # ..not followed by something that could be part of an atom # Atom | # or " # " [^\\\x80-\xff\n\015"] * # normal (?: \\ [^\x80-\xff] [^\\\x80-\xff\n\015"] * )* # ( special normal* )* " # " # Quoted string ) [\040\t]* # Nab whitespace. (?: \( # ( [^\\\x80-\xff\n\015()] * # normal* (?: # ( (?: \\ [^\x80-\xff] | \( # ( [^\\\x80-\xff\n\015()] * # normal* (?: \\ [^\x80-\xff] [^\\\x80-\xff\n\015()] * )* # (special normal*)* \) # ) ) # special [^\\\x80-\xff\n\015()] * # normal* )* # )* \) # ) [\040\t]* )* # If comment found, allow more spaces. # additional words )* @ [\040\t]* # Nab whitespace. (?: \( # ( [^\\\x80-\xff\n\015()] * # normal* (?: # ( (?: \\ [^\x80-\xff] | \( # ( [^\\\x80-\xff\n\015()] * # normal* (?: \\ [^\x80-\xff] [^\\\x80-\xff\n\015()] * )* # (special normal*)* \) # ) ) # special [^\\\x80-\xff\n\015()] * # normal* )* # )* \) # ) [\040\t]* )* # If comment found, allow more spaces. (?: [^(\040)<>@,;:".\\\[\]\000-\037\x80-\xff]+ # some number of atom characters... (?![^(\040)<>@,;:".\\\[\]\000-\037\x80-\xff]) # ..not followed by something that could be part of an atom | \[ # [ (?: [^\\\x80-\xff\n\015\[\]] | \\ [^\x80-\xff] )* # stuff \] # ] ) [\040\t]* # Nab whitespace. (?: \( # ( [^\\\x80-\xff\n\015()] * # normal* (?: # ( (?: \\ [^\x80-\xff] | \( # ( [^\\\x80-\xff\n\015()] * # normal* (?: \\ [^\x80-\xff] [^\\\x80-\xff\n\015()] * )* # (special normal*)* \) # ) ) # special [^\\\x80-\xff\n\015()] * # normal* )* # )* \) # ) [\040\t]* )* # If comment found, allow more spaces. # optional trailing comments (?: \. [\040\t]* # Nab whitespace. (?: \( # ( [^\\\x80-\xff\n\015()] * # normal* (?: # ( (?: \\ [^\x80-\xff] | \( # ( [^\\\x80-\xff\n\015()] * # normal* (?: \\ [^\x80-\xff] [^\\\x80-\xff\n\015()] * )* # (special normal*)* \) # ) ) # special [^\\\x80-\xff\n\015()] * # normal* )* # )* \) # ) [\040\t]* )* # If comment found, allow more spaces. (?: [^(\040)<>@,;:".\\\[\]\000-\037\x80-\xff]+ # some number of atom characters... (?![^(\040)<>@,;:".\\\[\]\000-\037\x80-\xff]) # ..not followed by something that could be part of an atom | \[ # [ (?: [^\\\x80-\xff\n\015\[\]] | \\ [^\x80-\xff] )* # stuff \] # ] ) [\040\t]* # Nab whitespace. (?: \( # ( [^\\\x80-\xff\n\015()] * # normal* (?: # ( (?: \\ [^\x80-\xff] | \( # ( [^\\\x80-\xff\n\015()] * # normal* (?: \\ [^\x80-\xff] [^\\\x80-\xff\n\015()] * )* # (special normal*)* \) # ) ) # special [^\\\x80-\xff\n\015()] * # normal* )* # )* \) # ) [\040\t]* )* # If comment found, allow more spaces. # optional trailing comments )* # address | # or (?: [^(\040)<>@,;:".\\\[\]\000-\037\x80-\xff]+ # some number of atom characters... (?![^(\040)<>@,;:".\\\[\]\000-\037\x80-\xff]) # ..not followed by something that could be part of an atom # Atom | # or " # " [^\\\x80-\xff\n\015"] * # normal (?: \\ [^\x80-\xff] [^\\\x80-\xff\n\015"] * )* # ( special normal* )* " # " # Quoted string ) # leading word [^()<>@,;:".\\\[\]\x80-\xff\000-\010\012-\037] * # "normal" atoms and or spaces (?: (?: \( # ( [^\\\x80-\xff\n\015()] * # normal* (?: # ( (?: \\ [^\x80-\xff] | \( # ( [^\\\x80-\xff\n\015()] * # normal* (?: \\ [^\x80-\xff] [^\\\x80-\xff\n\015()] * )* # (special normal*)* \) # ) ) # special [^\\\x80-\xff\n\015()] * # normal* )* # )* \) # ) | " # " [^\\\x80-\xff\n\015"] * # normal (?: \\ [^\x80-\xff] [^\\\x80-\xff\n\015"] * )* # ( special normal* )* " # " ) # "special" comment or quoted string [^()<>@,;:".\\\[\]\x80-\xff\000-\010\012-\037] * # more "normal" )* < [\040\t]* # Nab whitespace. (?: \( # ( [^\\\x80-\xff\n\015()] * # normal* (?: # ( (?: \\ [^\x80-\xff] | \( # ( [^\\\x80-\xff\n\015()] * # normal* (?: \\ [^\x80-\xff] [^\\\x80-\xff\n\015()] * )* # (special normal*)* \) # ) ) # special [^\\\x80-\xff\n\015()] * # normal* )* # )* \) # ) [\040\t]* )* # If comment found, allow more spaces. # < (?: @ [\040\t]* # Nab whitespace. (?: \( # ( [^\\\x80-\xff\n\015()] * # normal* (?: # ( (?: \\ [^\x80-\xff] | \( # ( [^\\\x80-\xff\n\015()] * # normal* (?: \\ [^\x80-\xff] [^\\\x80-\xff\n\015()] * )* # (special normal*)* \) # ) ) # special [^\\\x80-\xff\n\015()] * # normal* )* # )* \) # ) [\040\t]* )* # If comment found, allow more spaces. (?: [^(\040)<>@,;:".\\\[\]\000-\037\x80-\xff]+ # some number of atom characters... (?![^(\040)<>@,;:".\\\[\]\000-\037\x80-\xff]) # ..not followed by something that could be part of an atom | \[ # [ (?: [^\\\x80-\xff\n\015\[\]] | \\ [^\x80-\xff] )* # stuff \] # ] ) [\040\t]* # Nab whitespace. (?: \( # ( [^\\\x80-\xff\n\015()] * # normal* (?: # ( (?: \\ [^\x80-\xff] | \( # ( [^\\\x80-\xff\n\015()] * # normal* (?: \\ [^\x80-\xff] [^\\\x80-\xff\n\015()] * )* # (special normal*)* \) # ) ) # special [^\\\x80-\xff\n\015()] * # normal* )* # )* \) # ) [\040\t]* )* # If comment found, allow more spaces. # optional trailing comments (?: \. [\040\t]* # Nab whitespace. (?: \( # ( [^\\\x80-\xff\n\015()] * # normal* (?: # ( (?: \\ [^\x80-\xff] | \( # ( [^\\\x80-\xff\n\015()] * # normal* (?: \\ [^\x80-\xff] [^\\\x80-\xff\n\015()] * )* # (special normal*)* \) # ) ) # special [^\\\x80-\xff\n\015()] * # normal* )* # )* \) # ) [\040\t]* )* # If comment found, allow more spaces. (?: [^(\040)<>@,;:".\\\[\]\000-\037\x80-\xff]+ # some number of atom characters... (?![^(\040)<>@,;:".\\\[\]\000-\037\x80-\xff]) # ..not followed by something that could be part of an atom | \[ # [ (?: [^\\\x80-\xff\n\015\[\]] | \\ [^\x80-\xff] )* # stuff \] # ] ) [\040\t]* # Nab whitespace. (?: \( # ( [^\\\x80-\xff\n\015()] * # normal* (?: # ( (?: \\ [^\x80-\xff] | \( # ( [^\\\x80-\xff\n\015()] * # normal* (?: \\ [^\x80-\xff] [^\\\x80-\xff\n\015()] * )* # (special normal*)* \) # ) ) # special [^\\\x80-\xff\n\015()] * # normal* )* # )* \) # ) [\040\t]* )* # If comment found, allow more spaces. # optional trailing comments )* (?: , [\040\t]* # Nab whitespace. (?: \( # ( [^\\\x80-\xff\n\015()] * # normal* (?: # ( (?: \\ [^\x80-\xff] | \( # ( [^\\\x80-\xff\n\015()] * # normal* (?: \\ [^\x80-\xff] [^\\\x80-\xff\n\015()] * )* # (special normal*)* \) # ) ) # special [^\\\x80-\xff\n\015()] * # normal* )* # )* \) # ) [\040\t]* )* # If comment found, allow more spaces. @ [\040\t]* # Nab whitespace. (?: \( # ( [^\\\x80-\xff\n\015()] * # normal* (?: # ( (?: \\ [^\x80-\xff] | \( # ( [^\\\x80-\xff\n\015()] * # normal* (?: \\ [^\x80-\xff] [^\\\x80-\xff\n\015()] * )* # (special normal*)* \) # ) ) # special [^\\\x80-\xff\n\015()] * # normal* )* # )* \) # ) [\040\t]* )* # If comment found, allow more spaces. (?: [^(\040)<>@,;:".\\\[\]\000-\037\x80-\xff]+ # some number of atom characters... (?![^(\040)<>@,;:".\\\[\]\000-\037\x80-\xff]) # ..not followed by something that could be part of an atom | \[ # [ (?: [^\\\x80-\xff\n\015\[\]] | \\ [^\x80-\xff] )* # stuff \] # ] ) [\040\t]* # Nab whitespace. (?: \( # ( [^\\\x80-\xff\n\015()] * # normal* (?: # ( (?: \\ [^\x80-\xff] | \( # ( [^\\\x80-\xff\n\015()] * # normal* (?: \\ [^\x80-\xff] [^\\\x80-\xff\n\015()] * )* # (special normal*)* \) # ) ) # special [^\\\x80-\xff\n\015()] * # normal* )* # )* \) # ) [\040\t]* )* # If comment found, allow more spaces. # optional trailing comments (?: \. [\040\t]* # Nab whitespace. (?: \( # ( [^\\\x80-\xff\n\015()] * # normal* (?: # ( (?: \\ [^\x80-\xff] | \( # ( [^\\\x80-\xff\n\015()] * # normal* (?: \\ [^\x80-\xff] [^\\\x80-\xff\n\015()] * )* # (special normal*)* \) # ) ) # special [^\\\x80-\xff\n\015()] * # normal* )* # )* \) # ) [\040\t]* )* # If comment found, allow more spaces. (?: [^(\040)<>@,;:".\\\[\]\000-\037\x80-\xff]+ # some number of atom characters... (?![^(\040)<>@,;:".\\\[\]\000-\037\x80-\xff]) # ..not followed by something that could be part of an atom | \[ # [ (?: [^\\\x80-\xff\n\015\[\]] | \\ [^\x80-\xff] )* # stuff \] # ] ) [\040\t]* # Nab whitespace. (?: \( # ( [^\\\x80-\xff\n\015()] * # normal* (?: # ( (?: \\ [^\x80-\xff] | \( # ( [^\\\x80-\xff\n\015()] * # normal* (?: \\ [^\x80-\xff] [^\\\x80-\xff\n\015()] * )* # (special normal*)* \) # ) ) # special [^\\\x80-\xff\n\015()] * # normal* )* # )* \) # ) [\040\t]* )* # If comment found, allow more spaces. # optional trailing comments )* )* # additional domains : [\040\t]* # Nab whitespace. (?: \( # ( [^\\\x80-\xff\n\015()] * # normal* (?: # ( (?: \\ [^\x80-\xff] | \( # ( [^\\\x80-\xff\n\015()] * # normal* (?: \\ [^\x80-\xff] [^\\\x80-\xff\n\015()] * )* # (special normal*)* \) # ) ) # special [^\\\x80-\xff\n\015()] * # normal* )* # )* \) # ) [\040\t]* )* # If comment found, allow more spaces. # optional trailing comments )? # optional route (?: [^(\040)<>@,;:".\\\[\]\000-\037\x80-\xff]+ # some number of atom characters... (?![^(\040)<>@,;:".\\\[\]\000-\037\x80-\xff]) # ..not followed by something that could be part of an atom # Atom | # or " # " [^\\\x80-\xff\n\015"] * # normal (?: \\ [^\x80-\xff] [^\\\x80-\xff\n\015"] * )* # ( special normal* )* " # " # Quoted string ) [\040\t]* # Nab whitespace. (?: \( # ( [^\\\x80-\xff\n\015()] * # normal* (?: # ( (?: \\ [^\x80-\xff] | \( # ( [^\\\x80-\xff\n\015()] * # normal* (?: \\ [^\x80-\xff] [^\\\x80-\xff\n\015()] * )* # (special normal*)* \) # ) ) # special [^\\\x80-\xff\n\015()] * # normal* )* # )* \) # ) [\040\t]* )* # If comment found, allow more spaces. (?: \. [\040\t]* # Nab whitespace. (?: \( # ( [^\\\x80-\xff\n\015()] * # normal* (?: # ( (?: \\ [^\x80-\xff] | \( # ( [^\\\x80-\xff\n\015()] * # normal* (?: \\ [^\x80-\xff] [^\\\x80-\xff\n\015()] * )* # (special normal*)* \) # ) ) # special [^\\\x80-\xff\n\015()] * # normal* )* # )* \) # ) [\040\t]* )* # If comment found, allow more spaces. (?: [^(\040)<>@,;:".\\\[\]\000-\037\x80-\xff]+ # some number of atom characters... (?![^(\040)<>@,;:".\\\[\]\000-\037\x80-\xff]) # ..not followed by something that could be part of an atom # Atom | # or " # " [^\\\x80-\xff\n\015"] * # normal (?: \\ [^\x80-\xff] [^\\\x80-\xff\n\015"] * )* # ( special normal* )* " # " # Quoted string ) [\040\t]* # Nab whitespace. (?: \( # ( [^\\\x80-\xff\n\015()] * # normal* (?: # ( (?: \\ [^\x80-\xff] | \( # ( [^\\\x80-\xff\n\015()] * # normal* (?: \\ [^\x80-\xff] [^\\\x80-\xff\n\015()] * )* # (special normal*)* \) # ) ) # special [^\\\x80-\xff\n\015()] * # normal* )* # )* \) # ) [\040\t]* )* # If comment found, allow more spaces. # additional words )* @ [\040\t]* # Nab whitespace. (?: \( # ( [^\\\x80-\xff\n\015()] * # normal* (?: # ( (?: \\ [^\x80-\xff] | \( # ( [^\\\x80-\xff\n\015()] * # normal* (?: \\ [^\x80-\xff] [^\\\x80-\xff\n\015()] * )* # (special normal*)* \) # ) ) # special [^\\\x80-\xff\n\015()] * # normal* )* # )* \) # ) [\040\t]* )* # If comment found, allow more spaces. (?: [^(\040)<>@,;:".\\\[\]\000-\037\x80-\xff]+ # some number of atom characters... (?![^(\040)<>@,;:".\\\[\]\000-\037\x80-\xff]) # ..not followed by something that could be part of an atom | \[ # [ (?: [^\\\x80-\xff\n\015\[\]] | \\ [^\x80-\xff] )* # stuff \] # ] ) [\040\t]* # Nab whitespace. (?: \( # ( [^\\\x80-\xff\n\015()] * # normal* (?: # ( (?: \\ [^\x80-\xff] | \( # ( [^\\\x80-\xff\n\015()] * # normal* (?: \\ [^\x80-\xff] [^\\\x80-\xff\n\015()] * )* # (special normal*)* \) # ) ) # special [^\\\x80-\xff\n\015()] * # normal* )* # )* \) # ) [\040\t]* )* # If comment found, allow more spaces. # optional trailing comments (?: \. [\040\t]* # Nab whitespace. (?: \( # ( [^\\\x80-\xff\n\015()] * # normal* (?: # ( (?: \\ [^\x80-\xff] | \( # ( [^\\\x80-\xff\n\015()] * # normal* (?: \\ [^\x80-\xff] [^\\\x80-\xff\n\015()] * )* # (special normal*)* \) # ) ) # special [^\\\x80-\xff\n\015()] * # normal* )* # )* \) # ) [\040\t]* )* # If comment found, allow more spaces. (?: [^(\040)<>@,;:".\\\[\]\000-\037\x80-\xff]+ # some number of atom characters... (?![^(\040)<>@,;:".\\\[\]\000-\037\x80-\xff]) # ..not followed by something that could be part of an atom | \[ # [ (?: [^\\\x80-\xff\n\015\[\]] | \\ [^\x80-\xff] )* # stuff \] # ] ) [\040\t]* # Nab whitespace. (?: \( # ( [^\\\x80-\xff\n\015()] * # normal* (?: # ( (?: \\ [^\x80-\xff] | \( # ( [^\\\x80-\xff\n\015()] * # normal* (?: \\ [^\x80-\xff] [^\\\x80-\xff\n\015()] * )* # (special normal*)* \) # ) ) # special [^\\\x80-\xff\n\015()] * # normal* )* # )* \) # ) [\040\t]* )* # If comment found, allow more spaces. # optional trailing comments )* # address spec > # > # name and address ) /x Alan Other user\@dom.ain \"A. Other\" (a comment) A. Other (a comment) \"/s=user/ou=host/o=place/prmd=uu.yy/admd= /c=gb/\"\@x400-re.lay A missing angle ]{0,})>]{0,})>([\d]{0,}\.)(.*)((
([\w\W\s\d][^<>]{0,})|[\s]{0,}))<\/a><\/TD>]{0,})>([\w\W\s\d][^<>]{0,})<\/TD>]{0,})>([\w\W\s\d][^<>]{0,})<\/TD><\/TR>/is 43.
Word Processor
(N-1286)
Lega lstaff.comCA - Statewide /a[^a]b/ acb a\nb /a.b/ acb a\nb /a[^a]b/s acb a\nb /a.b/s acb a\nb /^(b+?|a){1,2}?c/ bac bbac bbbac bbbbac bbbbbac /^(b+|a){1,2}?c/ bac bbac bbbac bbbbac bbbbbac /(?!\A)x/m x\nb\n a\bx\n /\x0{ab}/ \0{ab} /(A|B)*?CD/ CD /(A|B)*CD/ CD /(AB)*?\1/ ABABAB /(AB)*\1/ ABABAB /(/ doesn't matter /(x)\2/ doesn't matter /((a{0,5}){0,5}){0,5}[c]/ aaaaaaaaaac aaaaaaaaaa /((a{0,5}){0,5})*[c]/ aaaaaaaaaac aaaaaaaaaa /(\b)*a/ a /(a)*b/ ab /(a|)*b/ ab b x /^(?:(a)|(b))*\1\2$/ abab /abc[^x]def/ abcxabcydef /^(a|\1x)*$/ aax aaxa // @{['']} /^(?:(a)|(b))*$/ ab /[\0]/ a \0 /[\1]/ a \1 /\10()()()()()()()()()/ doesn't matter /\10()()()()()()()()()()/ a /a(?<)b/ ab /[]/ doesn't matter /[\]/ doesn't matter /()/ a /[\x]/ x \0 /((a)*)*/ a /()a\1/ a /a\1()/ a /a(?i)a(?-i)a/ aaa aAa aAA /a(?i)a(?-i)a(?i)a(?-i)a/ aaaaa aAaAa AaAaA aAAAa AaaaA AAAAA aaAAA AAaaa /\x/ a X \0 /[a-c-e]/ a b d - /[b-\d]/ b c d - 1 /[\d-f]/ d e f - 1 /[/ doesn't matter /]/ ] a /[]/ doesn't matter /[-a-c]/ - a b d /[a-c-]/ - a b d /[-]/ a - /[--]/ a - /[---]/ a - /[--b]/ - a c /[b--]/ doesn't matter /a{/ a{ /a{}/ a{} /a{3/ a{3 /a{3,/ a{3, /a{3, 3}/ a{3,3} a{3, 3} aaa /a{3, 3}/x a{3,3} a{3, 3} aaa /a{3, }/ a{3,} a{3, } aaa /a{3, }/x a{3,} a{3, } aaa /\x x/ \0 x \0x /\x x/x \0 x \0x /\x 3/ \0003 \000 3 x3 x 3 /\x 3/x \0003 \000 3 x3 x 3 /^a{ 1}$/ a a{ 1} a{1} /^a{ 1}$/x a a{ 1} a{1} /{}/ {} a /{1}/ doesn't matter /*/ doesn't matter /|/ x /\0000/ \0000 /a(?<)b/ ab /a(?i)b/ ab aB Ab /a(?i=a)/ doesn't matter /a(?<=a){3000}a/ aa xa ax /a(?!=a){3000}a/ aa ax xa /a(){3000}a/ aa ax xa /a(?:){3000}a/ aa ax /a(?<=a)*a/ aa ax xa /a(?!=a)*a/ aa ax xa /a()*a/ aa ax xa /a(?:)*a/ aa ax xa /x(?<=a)*a/ aa xa ax /a(?<=(a))*\1/ aa /a(?<=(a))*?\1/ aa /(?=(a)\1)*aa/ aa /^((a|b){2,5}){2}$/ aaaaabbbbb /^(b*|ba){1,2}bc/ babc bbabc bababc bababbc babababc /^a{4,5}(?:c|a)c$/ aaaaac aaaaaac /^(a|){4,5}(?:c|a)c$/ aaaaac aaaaaac /(?m:^).abc$/ eeexabc eee\nxabc /(?m:^)abc/ abc \nabc /^abc/ abc \nabc /\Aabc/ abc \nabc /(?.*/)foo" /this/is/a/very/long/line/in/deed/with/very/many/slashes/in/it/you/see/ "(?>.*/)foo" /this/is/a/very/long/line/in/deed/with/very/many/slashes/in/and/foo /(?>(\.\d\d[1-9]?))\d+/ 1.230003938 1.875000282 1.235 /^((?>\w+)|(?>\s+))*$/ now is the time for all good men to come to the aid of the party this is not a line with only words and spaces! /(\d+)(\w)/ 12345a 12345+ /((?>\d+))(\w)/ 12345a 12345+ /(?>a+)b/ aaab /((?>a+)b)/ aaab /(?>(a+))b/ aaab /(?>b)+/ aaabbbccc /(?>a+|b+|c+)*c/ aaabbbbccccd /((?>[^()]+)|\([^()]*\))+/ ((abc(ade)ufh()()x /\(((?>[^()]+)|\([^()]+\))+\)/ (abc) (abc(def)xyz) ((()aaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaa /a(?-i)b/i ab Ab aB AB /(a (?x)b c)d e/ a bcd e a b cd e abcd e a bcde /(a b(?x)c d (?-x)e f)/ a bcde f abcdef /(a(?i)b)c/ abc aBc abC aBC Abc ABc ABC AbC /a(?i:b)c/ abc aBc ABC abC aBC /a(?i:b)*c/ aBc aBBc aBC aBBC /a(?=b(?i)c)\w\wd/ abcd abCd aBCd abcD /(?s-i:more.*than).*million/i more than million more than MILLION more \n than Million MORE THAN MILLION more \n than \n million /(?:(?s-i)more.*than).*million/i more than million more than MILLION more \n than Million MORE THAN MILLION more \n than \n million /(?>a(?i)b+)+c/ abc aBbc aBBc Abc abAb abbC /(?=a(?i)b)\w\wc/ abc aBc Ab abC aBC /(?<=a(?i)b)(\w\w)c/ abxxc aBxxc Abxxc ABxxc abxxC /(?:(a)|b)(?(1)A|B)/ aA bB aB bA /^(a)?(?(1)a|b)+$/ aa b bb ab /^(?(?=abc)\w{3}:|\d\d)$/ abc: 12 123 xyz /^(?(?!abc)\d\d|\w{3}:)$/ abc: 12 123 xyz /(?(?<=foo)bar|cat)/ foobar cat fcat focat foocat /(?(?a*)*/ a aa aaaa /(abc|)+/ abc abcabc abcabcabc xyz /([a]*)*/ a aaaaa /([ab]*)*/ a b ababab aaaabcde bbbb /([^a]*)*/ b bbbb aaa /([^ab]*)*/ cccc abab /([a]*?)*/ a aaaa /([ab]*?)*/ a b abab baba /([^a]*?)*/ b bbbb aaa /([^ab]*?)*/ c cccc baba /(?>a*)*/ a aaabcde /((?>a*))*/ aaaaa aabbaa /((?>a*?))*/ aaaaa aabbaa /(?(?=[^a-z]+[a-z]) \d{2}-[a-z]{3}-\d{2} | \d{2}-\d{2}-\d{2} ) /x 12-sep-98 12-09-98 sep-12-98 /(?<=(foo))bar\1/ foobarfoo foobarfootling foobar barfoo /(?i:saturday|sunday)/ saturday sunday Saturday Sunday SATURDAY SUNDAY SunDay /(a(?i)bc|BB)x/ abcx aBCx bbx BBx abcX aBCX bbX BBX /^([ab](?i)[cd]|[ef])/ ac aC bD elephant Europe frog France Africa /^(ab|a(?i)[b-c](?m-i)d|x(?i)y|z)/ ab aBd xy xY zebra Zambesi aCD XY /(?<=foo\n)^bar/m foo\nbar bar baz\nbar /(?<=(?]&/ <&OUT /^(a\1?){4}$/ aaaaaaaaaa AB aaaaaaaaa aaaaaaaaaaa /^(a(?(1)\1)){4}$/ aaaaaaaaaa aaaaaaaaa aaaaaaaaaaa /(?:(f)(o)(o)|(b)(a)(r))*/ foobar /(?<=a)b/ ab cb b /(?a+)ab/ /(?>a+)b/ aaab /([[:]+)/ a:[b]: /([[=]+)/ a=[b]= /([[.]+)/ a.[b]. /((?>a+)b)/ aaab /(?>(a+))b/ aaab /((?>[^()]+)|\([^()]*\))+/ ((abc(ade)ufh()()x /a\Z/ aaab a\nb\n /b\Z/ a\nb\n /b\z/ /b\Z/ a\nb /b\z/ a\nb /^(?>(?(1)\.|())[^\W_](?>[a-z0-9-]*[^\W_])?)+$/ a abc a-b 0-9 a.b 5.6.7 the.quick.brown.fox a100.b200.300c 12-ab.1245 \ .a -a a- a. a_b a.- a.. ab..bc the.quick.brown.fox- the.quick.brown.fox. the.quick.brown.fox_ the.quick.brown.fox+ /(?>.*)(?<=(abcd|wxyz))/ alphabetabcd endingwxyz a rather long string that doesn't end with one of them /word (?>(?:(?!otherword)[a-zA-Z0-9]+ ){0,30})otherword/ word cat dog elephant mussel cow horse canary baboon snake shark otherword word cat dog elephant mussel cow horse canary baboon snake shark /word (?>[a-zA-Z0-9]+ ){0,30}otherword/ word cat dog elephant mussel cow horse canary baboon snake shark the quick brown fox and the lazy dog and several other words getting close to thirty by now I hope /(?<=\d{3}(?!999))foo/ 999foo 123999foo 123abcfoo /(?<=(?!...999)\d{3})foo/ 999foo 123999foo 123abcfoo /(?<=\d{3}(?!999)...)foo/ 123abcfoo 123456foo 123999foo /(?<=\d{3}...)(?\s*)=(?>\s*) # find Z)+|A)*/ ZABCDEFG /((?>)+|A)*/ ZABCDEFG /a*/g abbab /^[a-\d]/ abcde -things 0digit bcdef /^[\d-a]/ abcde -things 0digit bcdef /(?<=abc).*(?=def)/ abcdef abcxdef abcxdefxdef /(?<=abc).*?(?=def)/ abcdef abcxdef abcxdefxdef /(?<=abc).+(?=def)/ abcdef abcxdef abcxdefxdef /(?<=abc).+?(?=def)/ abcdef abcxdef abcxdefxdef /(?<=\b)(.*)/ -abcdef abcdef /(?<=\B)(.*)/ -abcdef abcdef /^'[ab]'/ 'a' 'b' x'a' 'a'x 'ab' /^'[ab]'$/ 'a' 'b' x'a' 'a'x 'ab' /'[ab]'$/ 'a' 'b' x'a' 'a'x 'ab' /'[ab]'/ 'a' 'b' x'a' 'a'x 'ab' /abc\E/ abc abcE /abc[\Ex]/ abcx abcE /^\Qa*\E$/ a* a /\Qa*x\E/ a*x a* /\Qa*x/ a*x a* /\Q\Qa*x\E\E/ a*x a\\*x /\Q\Qa*x\E/ a*x a\\*x /a\Q[x\E]/ a[x] ax /a#comment\Q... {2}/x a aa /a(?#comment\Q... ){2}/x a aa /(?x)a#\Q ./ a. aa /ab(?=.*q)cd/ abcdxklqj /a(?!.*$)b/ ab /.{2}[a-z]/ Axicl-ppcre-2.0.3/test/simple0000644000175700010010000003473311041477700013645 0ustar ediNone;;; -*- Mode: LISP; Syntax: COMMON-LISP; Package: CL-PPCRE-TEST; Base: 10 -*- ;;; $Header: /usr/local/cvsrep/cl-ppcre/test/simple,v 1.9 2008/07/23 00:48:00 edi Exp $ ;;; some simple tests for CL-PPCRE - entered manually and to be read ;;; in the CL-PPCRE-TEST package; all forms are expected to return a ;;; true value on success when EVALuated (equalp (multiple-value-list (scan "(a)*b" "xaaabd")) (list 1 5 #(3) #(4))) (equalp (multiple-value-list (scan "(a)*b" "xaaabd" :start 1)) (list 1 5 #(3) #(4))) (equalp (multiple-value-list (scan "(a)*b" "xaaabd" :start 2)) (list 2 5 #(3) #(4))) (null (scan "(a)*b" "xaaabd" :end 4)) (equalp (multiple-value-list (scan '(:greedy-repetition 0 nil #\b) "bbbc")) (list 0 3 #() #())) (null (scan '(:greedy-repetition 4 6 #\b) "bbbc")) (let ((s (create-scanner "(([a-c])+)x"))) (equalp (multiple-value-list (scan s "abcxy")) (list 0 4 #(0 2) #(3 3)))) (equalp (multiple-value-list (scan-to-strings "[^b]*b" "aaabd")) (list "aaab" #())) (equalp (multiple-value-list (scan-to-strings "([^b])*b" "aaabd")) (list "aaab" #("a"))) (equalp (multiple-value-list (scan-to-strings "(([^b])*)b" "aaabd")) (list "aaab" #("aaa" "a"))) (equalp (register-groups-bind (first second third fourth) ("((a)|(b)|(c))+" "abababc" :sharedp t) (list first second third fourth)) (list "c" "a" "b" "c")) (equalp (register-groups-bind (nil second third fourth) ("((a)|(b)|(c))()+" "abababc" :start 6) (list second third fourth)) (list nil nil "c")) (null (register-groups-bind (first) ("(a|b)+" "accc" :start 1) first)) (equalp (register-groups-bind (fname lname (#'parse-integer date month year)) ("(\\w+)\\s+(\\w+)\\s+(\\d{1,2})\\.(\\d{1,2})\\.(\\d{4})" "Frank Zappa 21.12.1940") (list fname lname (encode-universal-time 0 0 0 date month year 0))) (list "Frank" "Zappa" 1292889600)) (flet ((foo (regex target-string &key (start 0) (end (length target-string))) (let ((sum 0)) (do-matches (s e regex target-string nil :start start :end end) (incf sum (- e s))) (/ sum (- end start))))) (and (= 1/3 (foo "a" "abcabcabc")) (= 5/9 (foo "aa|b" "aacabcbbc")))) (labels ((crossfoot (target-string &key (start 0) (end (length target-string))) (let ((sum 0)) (do-matches-as-strings (m :digit-class target-string nil :start start :end end) (incf sum (parse-integer m))) (if (< sum 10) sum (crossfoot (format nil "~A" sum)))))) (and (zerop (crossfoot "bar")) (= 3 (crossfoot "a3x")) (= 6 (crossfoot "12345")))) (let (result) (do-register-groups (first second third fourth) ("((a)|(b)|(c))" "abababc" nil :start 2 :sharedp t) (push (list first second third fourth) result)) (equal (nreverse result) '(("a" "a" nil nil) ("b" nil "b" nil) ("a" "a" nil nil) ("b" nil "b" nil) ("c" nil nil "c")))) (let (result) (do-register-groups ((#'parse-integer n) (#'intern sign) whitespace) ("(\\d+)|(\\+|-|\\*|/)|(\\s+)" "12*15 - 42/3") (unless whitespace (push (or n sign) result))) (equal (nreverse result) '(12 * 15 - 42 / 3))) (equal (all-matches "a" "foo bar baz") (list 5 6 9 10)) (equal (all-matches "\\w*" "foo bar baz") (list 0 3 3 3 4 7 7 7 8 11 11 11)) (equal (all-matches-as-strings "a" "foo bar baz") (list "a" "a")) (equal (all-matches-as-strings "\\w*" "foo bar baz") (list "foo" "" "bar" "" "baz" "")) (equal (split "\\s+" "foo bar baz frob") '("foo" "bar" "baz" "frob")) (equal (split "\\s*" "foo bar baz") '("f" "o" "o" "b" "a" "r" "b" "a" "z")) (equal (split "(\\s+)" "foo bar baz") '("foo" "bar" "baz")) (equal (split "(\\s+)" "foo bar baz" :with-registers-p t) '("foo" " " "bar" " " "baz")) (equal (split "(\\s)(\\s*)" "foo bar baz" :with-registers-p t) '("foo" " " "" "bar" " " " " "baz")) (equal (split "(,)|(;)" "foo,bar;baz" :with-registers-p t) '("foo" "," nil "bar" nil ";" "baz")) (equal (split "(,)|(;)" "foo,bar;baz" :with-registers-p t :omit-unmatched-p t) '("foo" "," "bar" ";" "baz")) (equal (split ":" "a:b:c:d:e:f:g::") '("a" "b" "c" "d" "e" "f" "g")) (equal (split ":" "a:b:c:d:e:f:g::" :limit 1) '("a:b:c:d:e:f:g::")) (equal (split ":" "a:b:c:d:e:f:g::" :limit 2) '("a" "b:c:d:e:f:g::")) (equal (split ":" "a:b:c:d:e:f:g::" :limit 3) '("a" "b" "c:d:e:f:g::")) (equal (split ":" "a:b:c:d:e:f:g::" :limit 1000) '("a" "b" "c" "d" "e" "f" "g" "" "")) (equal (multiple-value-list (regex-replace "fo+" "foo bar" "frob")) (list "frob bar" t)) (equal (multiple-value-list (regex-replace "fo+" "FOO bar" "frob")) (list "FOO bar" nil)) (equal (multiple-value-list (regex-replace "(?i)fo+" "FOO bar" "frob")) (list "frob bar" t)) (equal (multiple-value-list (regex-replace "(?i)fo+" "FOO bar" "frob" :preserve-case t)) (list "FROB bar" t)) (equal (multiple-value-list (regex-replace "(?i)fo+" "Foo bar" "frob" :preserve-case t)) (list "Frob bar" t)) (equal (multiple-value-list (regex-replace "bar" "foo bar baz" "[frob (was '\\&' between '\\`' and '\\'')]")) (list "foo [frob (was 'bar' between 'foo ' and ' baz')] baz" t)) (equal (multiple-value-list (regex-replace "bar" "foo bar baz" '("[frob (was '" :match "' between '" :before-match "' and '" :after-match "')]"))) (list "foo [frob (was 'bar' between 'foo ' and ' baz')] baz" t)) (equal (multiple-value-list (regex-replace "(be)(nev)(o)(lent)" "benevolent: adj. generous, kind" (lambda (match &rest registers) (format nil "~A [~{~A~^.~}]" match registers)) :simple-calls t)) (list "benevolent [be.nev.o.lent]: adj. generous, kind" t)) (equal (multiple-value-list (regex-replace-all "(?i)fo+" "foo Fooo FOOOO bar" "frob" :preserve-case t)) (list "frob Frob FROB bar" t)) (string= (regex-replace-all "(?i)f(o+)" "foo Fooo FOOOO bar" "fr\\1b" :preserve-case t) "froob Frooob FROOOOB bar") (let ((qp-regex (create-scanner "[\\x80-\\xff]"))) (flet ((encode-quoted-printable (string) "Converts 8-bit string to quoted-printable representation." ;; won't work for Corman Lisp because non-ASCII characters aren't 8-bit there (flet ((convert (target-string start end match-start match-end reg-starts reg-ends) (declare (ignore start end match-end reg-starts reg-ends)) (format nil "=~2,'0x" (char-code (char target-string match-start))))) (regex-replace-all qp-regex string #'convert)))) (string= (encode-quoted-printable "Fête Sørensen naïve Hühner Straße") "F=EAte S=F8rensen na=EFve H=FChner Stra=DFe"))) (let ((url-regex (create-scanner "[^a-zA-Z0-9_\\-.]"))) (flet ((url-encode (string) "URL-encodes a string." ;; won't work for Corman Lisp because non-ASCII characters aren't 8-bit there (flet ((convert (target-string start end match-start match-end reg-starts reg-ends) (declare (ignore start end match-end reg-starts reg-ends)) (format nil "%~2,'0x" (char-code (char target-string match-start))))) (regex-replace-all url-regex string #'convert)))) (string= (url-encode "Fête Sørensen naïve Hühner Straße") "F%EAte%20S%F8rensen%20na%EFve%20H%FChner%20Stra%DFe"))) (flet ((how-many (target-string start end match-start match-end reg-starts reg-ends) (declare (ignore target-string start end match-start match-end)) (format nil "~A" (- (svref reg-ends 0) (svref reg-starts 0))))) (string= (regex-replace-all "{(.+?)}" "foo{...}bar{.....}{..}baz{....}frob" (list "[" #'how-many " dots]")) "foo[3 dots]bar[5 dots][2 dots]baz[4 dots]frob")) (let ((qp-regex (create-scanner "[\\x80-\\xff]"))) (flet ((encode-quoted-printable (string) "Converts 8-bit string to quoted-printable representation. Version using SIMPLE-CALLS keyword argument." ;; ;; won't work for Corman Lisp because non-ASCII characters aren't 8-bit there (flet ((convert (match) (format nil "=~2,'0x" (char-code (char match 0))))) (regex-replace-all qp-regex string #'convert :simple-calls t)))) (string= (encode-quoted-printable "Fête Sørensen naïve Hühner Straße") "F=EAte S=F8rensen na=EFve H=FChner Stra=DFe"))) (flet ((how-many (match first-register) (declare (ignore match)) (format nil "~A" (length first-register)))) (string= (regex-replace-all "{(.+?)}" "foo{...}bar{.....}{..}baz{....}frob" (list "[" #'how-many " dots]") :simple-calls t) "foo[3 dots]bar[5 dots][2 dots]baz[4 dots]frob")) (flet ((my-repetition (char min) `(:greedy-repetition ,min nil ,char))) (setf (parse-tree-synonym 'a*) (my-repetition #\a 0) (parse-tree-synonym 'b+) (my-repetition #\b 1)) (unwind-protect (let ((scanner (create-scanner '(:sequence a* b+)))) (equal (mapcar (lambda (target) (scan scanner target)) '("ab" "b" "aab" "a" "x")) (list 0 0 0 nil nil))) (setf (parse-tree-synonym 'a*) nil (parse-tree-synonym 'b+) nil))) (null (scan "^a+$" "a+")) (let ((*allow-quoting* t)) ;;we use CREATE-SCANNER because of Lisps like SBCL that don't have an interpreter (equalp (multiple-value-list (scan (create-scanner "^\\Qa+\\E$") "a+")) (list 0 2 #() #()))) (string= (parse-string "\\k") "k") (let ((*allow-named-registers* t)) (equal (nth-value 1 (create-scanner "((?[a-z]*)(?[A-Z]*))")) (list nil "small" "big"))) (let ((*allow-named-registers* t)) (equal (nth-value 1 (create-scanner '(:register (:sequence (:named-register "small" (:greedy-repetition 0 nil (:char-class (:range #\a #\z)))) (:named-register "big" (:greedy-repetition 0 nil (:char-class (:range #\a #\z)))))))) (list nil "small" "big"))) (let ((*allow-named-registers* t)) (equalp (multiple-value-list (scan (create-scanner "((?[a-z]*)(?[A-Z]*))") "aaaBBB")) (list 0 6 #(0 0 3) #(6 3 6)))) (let ((*allow-named-registers* t)) ;; multiple-choice back-reference (equalp (multiple-value-list (scan (create-scanner "^(?[ab])(?[12])\\k\\k$") "a1aa")) (list 0 4 #(0 1) #(1 2)))) (let ((*allow-named-registers* t)) (equalp (multiple-value-list (scan (create-scanner "^(?[ab])(?[12])\\k\\k$") "a22a")) (list 0 4 #(0 1) #(1 2)))) (let ((*allow-named-registers* t)) ;; demonstrating most-recently-seen-register-first property of back-reference; ;; "greedy" regex (analogous to "aa?") (equalp (multiple-value-list (scan (create-scanner "^(?)(?a)(\\k)") "a")) (list 0 1 #(0 0 1) #(0 1 1)))) (let ((*allow-named-registers* t)) (equalp (multiple-value-list (scan (create-scanner "^(?)(?a)(\\k)") "aa")) (list 0 2 #(0 0 1) #(0 1 2)))) (let ((*allow-named-registers* t)) ;; switched groups ;; "lazy" regex (analogous to "aa??") (equalp (multiple-value-list (scan (create-scanner "^(?a)(?)(\\k)") "a")) (list 0 1 #(0 1 1) #(1 1 1)))) (let ((*allow-named-registers* t)) ;; scanner ignores the second "a" (equalp (multiple-value-list (scan (create-scanner "^(?a)(?)(\\k)") "aa")) (list 0 1 #(0 1 1) #(1 1 1)))) (let ((*allow-named-registers* t)) ;; "aa" will be matched only when forced by adding "$" at the end (equalp (multiple-value-list (scan (create-scanner "^(?a)(?)(\\k)$") "aa")) (list 0 2 #(0 1 1) #(1 1 2)))) (string= (quote-meta-chars "[a-z]*") "\\[a\\-z\\]\\*") (string= (handler-case (create-scanner "foo**x") (ppcre-syntax-error (condition) (format nil "Houston, we've got a problem with the string ~S: Looks like something went wrong at position ~A. The last message we received was \"~?\"." (ppcre-syntax-error-string condition) (ppcre-syntax-error-pos condition) (simple-condition-format-control condition) (simple-condition-format-arguments condition)))) "Houston, we've got a problem with the string \"foo**x\": Looks like something went wrong at position 4. The last message we received was \"Quantifier '*' not allowed.\".") (flet ((my-weird-filter (pos) "Only match at this point if either pos is odd and the character we're looking at is lowercase or if pos is even and the next two characters we're looking at are uppercase. Consume these characters if there's a match." (cond ((and (oddp pos) (< pos cl-ppcre::*end-pos*) (lower-case-p (char cl-ppcre::*string* pos))) (1+ pos)) ((and (evenp pos) (< (1+ pos) cl-ppcre::*end-pos*) (upper-case-p (char cl-ppcre::*string* pos)) (upper-case-p (char cl-ppcre::*string* (1+ pos)))) (+ pos 2)) (t nil)))) (let ((weird-regex `(:sequence "+" (:filter ,#'my-weird-filter) "+"))) (equalp (multiple-value-list (scan weird-regex "+A++a+AA+")) (list 5 9 #() #())))) (let ((a "\\E*")) (equalp (multiple-value-list (scan (concatenate 'string "(?:" (quote-meta-chars a) "){2}") "\\E*\\E*")) (list 0 6 #() #()))) (let ((a "\\E*")) (equalp (multiple-value-list (scan `(:greedy-repetition 2 2 ,a) "\\E*\\E*")) (list 0 6 #() #()))) (loop for *optimize-char-classes* in '(:hash-table :hash-table* :charset :charset* :charmap) for s = (create-scanner "(([a-c])+)x") always (equalp (multiple-value-list (scan s "abcxy")) (list 0 4 #(0 2) #(3 3)))) cl-ppcre-2.0.3/test/tests.lisp0000644000175700010010000001676711254505520014471 0ustar ediNone;;; -*- Mode: LISP; Syntax: COMMON-LISP; Package: CL-PPCRE-TEST; Base: 10 -*- ;;; $Header: /usr/local/cvsrep/cl-ppcre/test/tests.lisp,v 1.13 2009/09/17 19:17:36 edi Exp $ ;;; The tests in this file test CL-PPCRE against testdata generated by ;;; the Perl program `perltest.pl' from the input file `testinput' in ;;; order to check compatibility with Perl and correctness of the ;;; regex engine. ;;; Copyright (c) 2002-2009, Dr. Edmund Weitz. All rights reserved. ;;; Redistribution and use in source and binary forms, with or without ;;; modification, are permitted provided that the following conditions ;;; are met: ;;; * Redistributions of source code must retain the above copyright ;;; notice, this list of conditions and the following disclaimer. ;;; * Redistributions in binary form must reproduce the above ;;; copyright notice, this list of conditions and the following ;;; disclaimer in the documentation and/or other materials ;;; provided with the distribution. ;;; THIS SOFTWARE IS PROVIDED BY THE AUTHOR 'AS IS' AND ANY EXPRESSED ;;; OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED ;;; WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ;;; ARE DISCLAIMED. IN NO EVENT SHALL THE AUTHOR BE LIABLE FOR ANY ;;; DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL ;;; DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE ;;; GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS ;;; INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, ;;; WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING ;;; NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE OF THIS ;;; SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. (in-package :cl-ppcre-test) (defvar *this-file* (load-time-value (or #.*compile-file-pathname* *load-pathname*)) "The location of this source file.") (defmacro do-tests ((name &optional show-progress-p) &body body) "Helper macro which repeatedly executes BODY until the code in body calls the function DONE. It is assumed that each invocation of BODY will be the execution of one test which returns NIL in case of success and list of string describing errors otherwise. The macro prints a simple progress indicator \(one dots for ten tests) to *STANDARD-OUTPUT* unless SHOW-PROGRESS-P is NIL and returns a true value iff all tests succeeded. Errors in BODY are caught and reported \(and counted as failures)." `(let ((successp t) (testcount 1)) (block test-block (flet ((done () (return-from test-block successp))) (format t "~&Test: ~A~%" ,name) (loop (when (and ,show-progress-p (zerop (mod testcount 10))) (format t ".") (when (zerop (mod testcount 100)) (terpri)) (force-output)) (let ((errors (handler-case (progn ,@body) (error (msg) (list (format nil "~&got an unexpected error: ~A" msg)))))) (setq successp (and successp (null errors))) (when errors (format t "~&~4@A:~{~& ~A~}~%" testcount errors)) (incf testcount))))) successp)) (defun simple-tests (&key (file-name (make-pathname :name "simple" :type nil :version nil :defaults *this-file*)) (external-format '(:latin-1 :eol-style :lf)) verbose) "Loops through all the forms in the file FILE-NAME and executes each of them using EVAL. It is assumed that each FORM specifies a test which returns a true value iff it succeeds. Prints each test form to *STANDARD-OUTPUT* if VERBOSE is true and shows a simple progress indicator otherwise. EXTERNAL-FORMAT is the FLEXI-STREAMS external format which is used to read the file. Returns a true value iff all tests succeeded." (with-open-file (binary-stream file-name :element-type 'flex:octet) (let ((stream (flex:make-flexi-stream binary-stream :external-format external-format)) (*package* (find-package :cl-ppcre-test))) (do-tests ((format nil "Simple tests from file ~S" (file-namestring file-name)) (not verbose)) (let ((form (or (read stream nil) (done)))) (when verbose (format t "~&~S" form)) (cond ((eval form) nil) (t (list (format nil "~S returned NIL" form))))))))) (defun random-test-function (probability) "Returns a random character test function which contains each character with probability PROBABILITY." (let ((hash-table (make-hash-table))) (dotimes (code char-code-limit) (let ((char (code-char code))) (when (and char (< (random 1.0d0) probability)) (setf (gethash (code-char code) hash-table) t)))) (lambda (char) (gethash char hash-table)))) (defun test-optimized-test-functions% (probability) "Creates a random test function with probability PROBABILITY and six \(one for each possible \"kind\") corresponding optimized test functions, then checks for each character in turn that all functions agree on it." (let* ((test-function (random-test-function probability)) (optimized-functions (loop for kind in '(nil :hash-table :hash-table* :charset :charset* :charmap) collect (create-optimized-test-function test-function :kind kind)))) (loop for code below char-code-limit for char = (code-char code) for expected-result = (and char (funcall test-function char)) always (or (null char) (loop for optimized-function in optimized-functions always (eq (not (funcall optimized-function char)) (not expected-result))))))) (defun test-optimized-test-functions (&key verbose) "Runs TEST-OPTIMIZED-TEST-FUNCTIONS% with different probabilities." (let ((probabilities '(0 .001 .01 .1 1))) (do-tests ("Optimized test functions - this might take some time..." (not verbose)) (let ((probability (or (pop probabilities) (done)))) (when verbose (format t "~&Probability is ~A" probability)) (not (test-optimized-test-functions% probability)))))) (defun run-all-tests (&key more-tests verbose) "Runs all tests for CL-PPCRE and returns a true value iff all tests succeeded. VERBOSE is interpreted by the individual test suites. MORE-TESTS can be a list of function designators designating additional tests to run. This facility is used by the tests for CL-PPCRE-UNICODE." (let ((successp t)) (macrolet ((run-test-suite (&body body) `(unless (progn ,@body) (setq successp nil)))) ;; run the automatically generated Perl tests (run-test-suite (perl-test :verbose verbose)) (run-test-suite (test-optimized-test-functions :verbose verbose)) (run-test-suite (simple-tests :verbose verbose)) (when more-tests (unless (listp more-tests) (setq more-tests (list more-tests)) (dolist (test more-tests) (run-test-suite (funcall test :verbose verbose)))))) (format t "~2&~:[Some tests failed~;All tests passed~]." successp) successp)) cl-ppcre-2.0.3/test/unicode-tests.lisp0000644000175700010010000001101311041474261016071 0ustar ediNone;;; -*- Mode: LISP; Syntax: COMMON-LISP; Package: CL-PPCRE-TEST; Base: 10 -*- ;;; $Header: /usr/local/cvsrep/cl-ppcre/test/unicode-tests.lisp,v 1.8 2008/07/23 00:17:53 edi Exp $ ;;; Copyright (c) 2008, Dr. Edmund Weitz. All rights reserved. ;;; Redistribution and use in source and binary forms, with or without ;;; modification, are permitted provided that the following conditions ;;; are met: ;;; * Redistributions of source code must retain the above copyright ;;; notice, this list of conditions and the following disclaimer. ;;; * Redistributions in binary form must reproduce the above ;;; copyright notice, this list of conditions and the following ;;; disclaimer in the documentation and/or other materials ;;; provided with the distribution. ;;; THIS SOFTWARE IS PROVIDED BY THE AUTHOR 'AS IS' AND ANY EXPRESSED ;;; OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED ;;; WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ;;; ARE DISCLAIMED. IN NO EVENT SHALL THE AUTHOR BE LIABLE FOR ANY ;;; DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL ;;; DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE ;;; GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS ;;; INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, ;;; WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING ;;; NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE OF THIS ;;; SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. (in-package :cl-ppcre-test) (defun unicode-test (&key (file-name (make-pathname :name "unicodetestdata" :type nil :version nil :defaults *this-file*) file-name-provided-p) verbose) "Loops through all test cases in FILE-NAME and prints a report if VERBOSE is true. Returns a true value if all tests succeeded. For the syntax of the tests in FILE-NAME refer to CL-UNICODE." (with-open-file (stream file-name) (let ((*regex-char-code-limit* (if file-name-provided-p *regex-char-code-limit* char-code-limit)) (*optimize-char-classes* (if file-name-provided-p *optimize-char-classes* nil)) ;; we only check for correctness and don't care about speed ;; that match (but rather about space constraints of the ;; trial versions) (*use-bmh-matchers* (if file-name-provided-p *use-bmh-matchers* nil))) (do-tests ((format nil "Running Unicode tests in file ~S" (file-namestring file-name)) (not verbose)) (let ((input-line (or (read stream nil) (done))) errors) (destructuring-bind (char-code property-name expected-result) input-line (let ((char (and (< char-code char-code-limit) (code-char char-code)))) (when char (when verbose (format t "~&~A: #x~X" property-name char-code)) (let* ((string (string char)) (result-1 (scan (format nil "\\p{~A}" property-name) string)) (result-2 (scan (format nil "[\\p{~A}]" property-name) string)) (inverted-result-1 (scan (format nil "\\P{~A}" property-name) string)) (inverted-result-2 (scan (format nil "[\\P{~A}]" property-name) string))) (unless (eq expected-result (not (not result-1))) (push (format nil "\(code-char #x~X) should ~:[not ~;~]have matched \"\\p{~A}\"" char-code expected-result property-name) errors)) (unless (eq expected-result (not (not result-2))) (push (format nil "\(code-char #x~X) should ~:[not ~;~]have matched \"[\\p{~A}]\"" char-code expected-result property-name) errors)) (unless (eq expected-result (not inverted-result-1)) (push (format nil "\(code-char #x~X) should ~:[~;not ~]have matched \"\\P{~A}\"" char-code expected-result property-name) errors)) (unless (eq expected-result (not inverted-result-2)) (push (format nil "\(code-char #x~X) should ~:[~;not ~]have matched \"[\\P{~A}]\"" char-code expected-result property-name) errors))) errors)))))))) cl-ppcre-2.0.3/test/unicodetestdata0000644000175700010010000000562511041364003015521 0ustar ediNone;;; -*- Mode: LISP; Syntax: COMMON-LISP; Package: CL-USER; Base: 10 -*- ;;; $Header: /usr/local/cvsrep/cl-ppcre/test/unicodetestdata,v 1.10 2008/07/22 14:00:35 edi Exp $ ;;; some arbitrary test data for Unicode properties - stolen from CL-UNICODE (#x0001 "ASCII" t) (#x0100 "ASCII" nil) (#x000A "Alphabetic" nil) (#x0061 "Alphabetic" t) (#x0061 "Ll" t) (#x0041 "Alphabetic" t) (#x0041 "alphabetic" t) (#x0041 "IsAlphabetic" t) (#x02E4 "Alphabetic" t) (#x0970 "Alphabetic" nil) (#x030D "BidiClass:NonspacingMark" t) (#x030D "NonspacingMark" t) (#x030D "nonspacing mark" t) (#xE0146 "BidiClass:NonspacingMark" t) (#x000D "BidiClass:WhiteSpace" nil) (#x0020 "BidiClass:WhiteSpace" t) (#x2006 "BidiClass:WhiteSpace" t) (#x12470 "Cuneiform" t) (#x12470 "IsCuneiform" t) (#x12470 "CuneiformNumbersAndPunctuation" t) (#x12470 "Block:CuneiformNumbersAndPunctuation" t) (#x12470 "InCuneiformNumbersAndPunctuation" t) (#x12470 "Script:Cuneiform" t) (#x0041 "Block:Hebrew" nil) (#x0593 "Block:Hebrew" t) (#x0593 "InHebrew" t) (#x040D "Block:Cyrillic" t) (#x040D "InCyrillic" t) (#x0042 "Block:Cyrillic" nil) (#x2011 "Dash" t) (#x2011 "IsDash" t) (#xFF0D "Dash" t) (#x003D "Dash" nil) (#x00F0 "Lowercase" t) (#x00F0 "IsLowercase" t) (#x00F0 "lowercase" t) (#x00F0 "Ll" t) (#x0067 "Lowercase" t) (#x010A "Lowercase" nil) (#x1D6C1 "Lowercase" nil) (#x0023 "CurrencySymbol" nil) (#x0024 "CurrencySymbol" t) (#x0024 "IsCurrencySymbol" t) (#x0024 "currency symbol" t) (#x20AC "CurrencySymbol" t) (#xFFE6 "CurrencySymbol" t) (#x002B "Sm" t) (#x002B "Math" t) (#x002B "IsMath" t) (#x002B "math" t) (#x211C "Math" t) (#x1D7D2 "Math" t) (#x002A "Math" nil) (#x25C9 "Math" nil) (#x0000 "NonCharacterCodePoint" nil) (#xFDD0 "NonCharacterCodePoint" t) (#xFDD0 "Non-Character-Code-Point" t) (#xFDD0 "non-character-code-point" t) (#xFFFFF "NonCharacterCodePoint" t) (#x0043 "Arabic" nil) (#x0606 "Arabic" t) (#x0606 "arabic" t) (#x0606 "IsArabic" t) (#x0606 "Script:Arabic" t) (#x0044 "IsVariationSelector" nil) (#x0044 "VariationSelector" nil) (#x180B "VariationSelector" t) (#x180B "Variation_Selector" t) (#x180B "Variation-Selector" t) (#x180B "variationselector" t) (#x180B "variation selector" t) (#x180B "IsVariationSelector" t) (#x00B5 "XIDContinue" t) (#x00B5 "IsXIDContinue" t) (#x00B5 "IsXID_Continue" t) (#x00B5 "Is_XID_Continue" t) (#x00B5 "XID_Continue" t) (#x33FF "Unified_Ideograph" nil) (#x33FF "Ideographic" nil) (#x3400 "Unified_Ideograph" t) (#x3400 "Ideographic" t) (#x3400 "Han" t) (#x3400 "OtherLetter" t) (#x3400 "Alphabetic" t) (#x3400 "Common" nil) (#x3400 "Assigned" t) (#x3400 "Any" t) (#x0378 "Cn" t) (#x0378 "Unassigned" t) (#x0377 "Cn" nil) (#x0377 "Unassigned" nil) (#x2800 "Braille" t) (#x2800 "Script:Braille" t) (#x2800 "OtherSymbol" t) (#x0027 "QuotationMark" t) (#x201C "QuotationMark" t) (#x201C "OtherNeutral" t) (#x201C "PatternSyntax" t) (#x0028 "Bidi_Mirrored" t) (#x0028 "BidiMirrored" t) (#x0028 "IsBidiMirrored" t) (#x0027 "Bidi_Mirrored" nil) cl-ppcre-2.0.3/util.lisp0000644000175700010010000002027411271772157013324 0ustar ediNone;;; -*- Mode: LISP; Syntax: COMMON-LISP; Package: CL-PPCRE; Base: 10 -*- ;;; $Header: /usr/local/cvsrep/cl-ppcre/util.lisp,v 1.48 2009/10/28 07:36:15 edi Exp $ ;;; Utility functions and constants dealing with the character sets we ;;; use to encode character classes ;;; Copyright (c) 2002-2009, Dr. Edmund Weitz. All rights reserved. ;;; Redistribution and use in source and binary forms, with or without ;;; modification, are permitted provided that the following conditions ;;; are met: ;;; * Redistributions of source code must retain the above copyright ;;; notice, this list of conditions and the following disclaimer. ;;; * Redistributions in binary form must reproduce the above ;;; copyright notice, this list of conditions and the following ;;; disclaimer in the documentation and/or other materials ;;; provided with the distribution. ;;; THIS SOFTWARE IS PROVIDED BY THE AUTHOR 'AS IS' AND ANY EXPRESSED ;;; OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED ;;; WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ;;; ARE DISCLAIMED. IN NO EVENT SHALL THE AUTHOR BE LIABLE FOR ANY ;;; DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL ;;; DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE ;;; GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS ;;; INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, ;;; WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING ;;; NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE OF THIS ;;; SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. (in-package :cl-ppcre) (defmacro defconstant (name value &optional doc) "Make sure VALUE is evaluated only once \(to appease SBCL)." `(cl:defconstant ,name (if (boundp ',name) (symbol-value ',name) ,value) ,@(when doc (list doc)))) #+:lispworks (eval-when (:compile-toplevel :load-toplevel :execute) (import 'lw:with-unique-names)) #-:lispworks (defmacro with-unique-names ((&rest bindings) &body body) "Syntax: WITH-UNIQUE-NAMES ( { var | (var x) }* ) declaration* form* Executes a series of forms with each VAR bound to a fresh, uninterned symbol. The uninterned symbol is as if returned by a call to GENSYM with the string denoted by X - or, if X is not supplied, the string denoted by VAR - as argument. The variable bindings created are lexical unless special declarations are specified. The scopes of the name bindings and declarations do not include the Xs. The forms are evaluated in order, and the values of all but the last are discarded \(that is, the body is an implicit PROGN)." ;; reference implementation posted to comp.lang.lisp as ;; by Vebjorn Ljosa - see also ;; `(let ,(mapcar #'(lambda (binding) (check-type binding (or cons symbol)) (if (consp binding) (destructuring-bind (var x) binding (check-type var symbol) `(,var (gensym ,(etypecase x (symbol (symbol-name x)) (character (string x)) (string x))))) `(,binding (gensym ,(symbol-name binding))))) bindings) ,@body)) #+:lispworks (eval-when (:compile-toplevel :load-toplevel :execute) (setf (macro-function 'with-rebinding) (macro-function 'lw:rebinding))) #-:lispworks (defmacro with-rebinding (bindings &body body) "WITH-REBINDING ( { var | (var prefix) }* ) form* Evaluates a series of forms in the lexical environment that is formed by adding the binding of each VAR to a fresh, uninterned symbol, and the binding of that fresh, uninterned symbol to VAR's original value, i.e., its value in the current lexical environment. The uninterned symbol is created as if by a call to GENSYM with the string denoted by PREFIX - or, if PREFIX is not supplied, the string denoted by VAR - as argument. The forms are evaluated in order, and the values of all but the last are discarded \(that is, the body is an implicit PROGN)." ;; reference implementation posted to comp.lang.lisp as ;; by Vebjorn Ljosa - see also ;; (loop for binding in bindings for var = (if (consp binding) (car binding) binding) for name = (gensym) collect `(,name ,var) into renames collect ``(,,var ,,name) into temps finally (return `(let ,renames (with-unique-names ,bindings `(let (,,@temps) ,,@body)))))) (declaim (inline digit-char-p)) (defun digit-char-p (chr) (declare #.*standard-optimize-settings*) "Tests whether a character is a decimal digit, i.e. the same as Perl's [\\d]. Note that this function shadows the standard Common Lisp function CL:DIGIT-CHAR-P." (char<= #\0 chr #\9)) (declaim (inline word-char-p)) (defun word-char-p (chr) (declare #.*standard-optimize-settings*) "Tests whether a character is a \"word\" character. In the ASCII charset this is equivalent to a-z, A-Z, 0-9, or _, i.e. the same as Perl's [\\w]." (or (alphanumericp chr) (char= chr #\_))) (defconstant +whitespace-char-string+ (coerce '(#\Space #\Tab #\Linefeed #\Return #\Page) 'string) "A string of all characters which are considered to be whitespace. Same as Perl's [\\s].") (defun whitespacep (chr) (declare #.*special-optimize-settings*) "Tests whether a character is whitespace, i.e. whether it would match [\\s] in Perl." (find chr +whitespace-char-string+ :test #'char=)) (defmacro maybe-coerce-to-simple-string (string) "Coerces STRING to a simple STRING unless it already is one." (with-unique-names (=string=) `(let ((,=string= ,string)) (cond (#+:lispworks (lw:simple-text-string-p ,=string=) #-:lispworks (simple-string-p ,=string=) ,=string=) (t (coerce ,=string= #+:lispworks 'lw:simple-text-string #-:lispworks 'simple-string)))))) (declaim (inline nsubseq)) (defun nsubseq (sequence start &optional (end (length sequence))) "Returns a subsequence by pointing to location in original sequence." (make-array (- end start) :element-type (array-element-type sequence) :displaced-to sequence :displaced-index-offset start)) (defun normalize-var-list (var-list) "Utility function for REGISTER-GROUPS-BIND and DO-REGISTER-GROUPS. Creates the long form \(a list of \(FUNCTION VAR) entries) out of the short form of VAR-LIST." (loop for element in var-list if (consp element) nconc (loop for var in (rest element) collect (list (first element) var)) else collect (list '(function identity) element))) (defun string-list-to-simple-string (string-list) "Concatenates a list of strings to one simple-string." (declare #.*standard-optimize-settings*) ;; this function provided by JP Massar; note that we can't use APPLY ;; with CONCATENATE here because of CALL-ARGUMENTS-LIMIT (let ((total-size 0)) (declare (fixnum total-size)) (dolist (string string-list) #-:genera (declare (string string)) (incf total-size (length string))) (let ((result-string (make-sequence #-:lispworks 'simple-string #+:lispworks 'lw:simple-text-string total-size)) (curr-pos 0)) (declare (fixnum curr-pos)) (dolist (string string-list) #-:genera (declare (string string)) (replace result-string string :start1 curr-pos) (incf curr-pos (length string))) result-string))) (defun complement* (test-function) "Like COMPLEMENT but optimized for unary functions." (declare #.*standard-optimize-settings*) (typecase test-function (function (lambda (char) (declare (character char)) (not (funcall (the function test-function) char)))) (otherwise (lambda (char) (declare (character char)) (not (funcall test-function char))))))