3 ;;; Option parser, standard issue
5 ;;; (c) 2005 Straylight/Edgeware
8 ;;;----- Licensing notice ---------------------------------------------------
10 ;;; This file is part of the Sensible Object Design, an object system for C.
12 ;;; SOD is free software; you can redistribute it and/or modify
13 ;;; it under the terms of the GNU General Public License as published by
14 ;;; the Free Software Foundation; either version 2 of the License, or
15 ;;; (at your option) any later version.
17 ;;; SOD is distributed in the hope that it will be useful,
18 ;;; but WITHOUT ANY WARRANTY; without even the implied warranty of
19 ;;; MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
20 ;;; GNU General Public License for more details.
22 ;;; You should have received a copy of the GNU General Public License
23 ;;; along with SOD; if not, write to the Free Software Foundation,
24 ;;; Inc., 59 Temple Place - Suite 330, Boston, MA 02111-1307, USA.
26 (eval-when (:compile-toplevel :load-toplevel :execute)
27 (handler-bind ((warning #'muffle-warning))
28 (cl:defpackage #:optparse
29 (:use #:common-lisp #:sod-utilities))))
31 (cl:in-package #:optparse)
33 ;;;--------------------------------------------------------------------------
34 ;;; Program environment things.
36 (export '(*program-name* *command-line*))
37 (defvar *program-name* "<unknown>"
38 "Program name, as retrieved from the command line.")
39 (defvar *command-line* nil
40 "A list of command-line arguments, including the program name.")
42 (export 'set-command-line-arguments)
43 (defun set-command-line-arguments ()
44 "Retrieve command-line arguments.
46 Set `*command-line*' and `*program-name*'."
47 (setf *command-line* (cons (uiop:argv0) uiop:*command-line-arguments*)
48 *program-name* (pathname-name (car *command-line*))))
50 ;;;--------------------------------------------------------------------------
51 ;;; Fancy conditionals.
53 (eval-when (:compile-toplevel :load-toplevel :execute)
54 (defun do-case2-like (kind vform clauses)
55 "Helper function for `case2' and `ecase2'."
56 (with-gensyms (scrutinee argument)
57 `(multiple-value-bind (,scrutinee ,argument) ,vform
58 (declare (ignorable ,argument))
60 ,@(mapcar (lambda (clause)
62 (cases (&optional varx vary) &rest forms)
66 (list `(let ((,(or vary varx) ,argument)
68 `((,varx ,scrutinee))))
73 (defmacro case2 (vform &body clauses)
74 "Switch based on the first value of a form, capturing the second value.
76 VFORM is a form which evaluates to two values, SCRUTINEE and ARGUMENT.
77 The CLAUSES have the form (CASES ([[SCRUVAR] ARGVAR]) FORMS...), where a
78 standard `case' clause has the form (CASES FORMS...). The `case2' form
79 evaluates the VFORM, and compares the SCRUTINEE to the various CASES, in
80 order, just like `case'. If there is a match, then the corresponding
81 FORMs are evaluated with ARGVAR bound to the ARGUMENT and SCRUVAR bound to
82 the SCRUTINEE (where specified). Note the bizarre defaulting behaviour:
83 ARGVAR is less optional than SCRUVAR."
84 (do-case2-like 'case vform clauses))
86 (defmacro ecase2 (vform &body clauses)
87 "Like `case2', but signals an error if no clause matches the SCRUTINEE."
88 (do-case2-like 'ecase vform clauses))
90 ;;;--------------------------------------------------------------------------
91 ;;; Standard error-reporting functions.
94 (defun moan (msg &rest args)
95 "Report an error message in the usual way."
96 (format *error-output* "~&~A: ~?~%" *program-name* msg args))
99 (defun die (&rest args)
100 "Report an error message and exit."
104 ;;;--------------------------------------------------------------------------
105 ;;; The main option parser.
108 (defvar *options* nil
109 "The default list of command-line options.")
111 (export '(option optionp make-option
112 opt-short-name opt-long-name opt-tag opt-negated-tag
113 opt-arg-name opt-arg-optional-p opt-documentation))
114 (locally (declare #+sbcl (sb-ext:muffle-conditions style-warning))
121 (print-unreadable-object (o s :type t)
122 (format s "~*~:[~2:*~:[~3*~@[~S~]~
125 ~2*~@[~:*~:[ ~A~;[~A]~]~]~
129 ~*~@[~:*~:[=~A~;[=~A]~]~]~
133 (opt-arg-optional-p o)
135 (opt-%documentation o)))))
136 (:constructor %make-option
137 (&key long-name tag negated-tag short-name
138 arg-name arg-optional-p documentation
139 &aux (%documentation documentation)))
140 (:constructor make-option
141 (long-name short-name
143 &key (tag (intern (string-upcase
148 doc (documentation doc)
151 "Describes a command-line option. Slots:
153 LONG-NAME The option's long name. If this is null, the `option' is
154 just a banner to be printed in the program's help text.
156 TAG The value to be returned if this option is encountered. If
157 this is a function, instead, the function is called with the
158 option's argument or nil.
160 NEGATED-TAG As for TAG, but used if the negated form of the option is
161 found. If this is nil (the default), the option cannot be
164 SHORT-NAME The option's short name. This must be a single character, or
165 nil if the option has no short name.
167 ARG-NAME The name of the option's argument, a string. If this is nil,
168 the option doesn't accept an argument. The name is shown in
172 If non-nil, the option's argument is optional. This is
173 ignored unless ARG-NAME is non-null.
176 The help text for this option. It is automatically line-
177 wrapped. If nil, the option is omitted from the help
180 Usually, one won't use `make-option', but use the `option' macro instead."
181 (long-name nil :type (or null string))
183 (negated-tag nil :type t)
184 (short-name nil :type (or null character))
185 (arg-name nil :type (or null string))
186 (arg-optional-p nil :type t)
187 (%documentation nil :type (or null string))))
188 (define-access-wrapper opt-documentation opt-%documentation)
190 (export '(option-parser option-parser-p make-option-parser
191 op-options op-non-option op-long-only-p op-numeric-p
192 op-negated-numeric-p op-negated-p))
193 (defstruct (option-parser
195 (:constructor make-option-parser
196 (&key ((:args argstmp) (cdr *command-line*))
199 ((:numericp numeric-p))
202 &aux (args (cons nil argstmp))
205 (negated-p (or negated-numeric-p
206 (some #'opt-negated-tag
208 "An option parser object. Slots:
210 ARGS The arguments to be parsed. Usually this will be
213 OPTIONS List of option structures describing the acceptable options.
215 NON-OPTION Behaviour when encountering a non-option argument. The
216 default is :skip. Allowable values are:
217 :skip -- pretend that it appeared after the option
218 arguments; this is the default behaviour of GNU getopt
219 :stop -- stop parsing options, leaving the remaining
220 command line unparsed
221 :return -- return :non-option and the argument word
223 NUMERIC-P Non-nil tag (as for options) if numeric options (e.g., -43)
224 are to be allowed. The default is nil. (Anomaly: the
225 keyword for this argument is :numericp.)
228 Non-nil tag (as for options) if numeric options (e.g., -43)
229 can be negated. This is not the same thing as a negative
232 LONG-ONLY-P A misnomer inherited from GNU getopt. Whether to allow
233 long options to begin with a single dash. Short options are
234 still allowed, and may be cuddled as usual. The default is
236 (args nil :type list)
237 (%options nil :type list)
238 (non-option :skip :type (or function (member :skip :stop :return)))
239 (next nil :type list)
240 (short-opt nil :type (or null string))
241 (short-opt-index 0 :type fixnum)
242 (short-opt-neg-p nil :type t)
243 (long-only-p nil :type t)
244 (numeric-p nil :type t)
245 (negated-numeric-p nil :type t)
246 (negated-p nil :type t))
247 (define-access-wrapper op-options op-%options)
249 (export 'option-parse-error)
250 (define-condition option-parse-error (error simple-condition)
253 "Indicates an error found while parsing options.
255 Probably not that useful."))
257 (defun option-parse-error (msg &rest args)
258 "Signal an option-parse-error with the given message and arguments."
259 (error (make-condition 'option-parse-error
261 :format-arguments args)))
263 (export 'option-parse-remainder)
264 (defun option-parse-remainder (op)
265 "Returns the unparsed remainder of the command line."
268 (export 'option-parse-return)
269 (defun option-parse-return (tag &optional argument)
270 "Force a return from `option-parse-next' with TAG and ARGUMENT.
272 This should only be called from an option handler."
273 (throw 'option-parse-return (values tag argument)))
275 (export 'option-parse-next)
276 (defun option-parse-next (op)
277 "Parse and handle the next option from the command-line.
279 This is the main option-parsing function. OP is an option-parser object,
280 initialized appropriately. Returns two values, OPT and ARG: OPT is the
281 tag of the next option read, and ARG is the argument attached to it, or
282 nil if there was no argument. If there are no more options, returns nil
283 twice. Options whose TAG is a function aren't returned; instead, the tag
284 function is called, with the option argument (or nil) as the only
285 argument. It is safe for tag functions to throw out of
286 `option-parse-next', if they desparately need to. (This is the only way
287 to actually get `option-parse-next' to return a function value, should
288 that be what you want. See `option-parse-return' for a way of doing
291 While `option-parse-next' is running, there is a restart `skip-option'
292 which moves on to the next option. Error handlers should use this to
293 resume after parsing errors."
294 (labels ((ret (opt &optional arg)
295 (return-from option-parse-next (values opt arg)))
297 (setf (op-next op) nil)
305 (setf (op-next op) (cdr (op-next op))))
307 (setf (cdr (op-next op)) (cddr (op-next op))))
309 (prog1 (peek-arg) (eat-arg)))
311 (process-option (o name negp &key arg argfunc)
312 (cond ((not (opt-arg-name o))
315 "Option `~A' does not accept arguments"
319 (setf arg (funcall argfunc)))
320 ((opt-arg-optional-p o))
322 (setf arg (get-arg)))
324 (option-parse-error "Option `~A' requires an argument"
326 (let ((how (if negp (opt-negated-tag o) (opt-tag o))))
331 (process-long-option (arg start negp)
332 (when (and (not negp)
334 (> (length arg) (+ start 3))
336 :start1 start :end1 (+ start 3)))
340 (eqpos (position #\= arg :start start))
341 (len (or eqpos (length arg)))
342 (optname (subseq arg 0 len))
343 (len-2 (- len start)))
344 (dolist (o (op-options op))
345 (cond ((or (not (stringp (opt-long-name o)))
346 (and negp (not (opt-negated-tag o)))
347 (< (length (opt-long-name o)) len-2)
348 (string/= optname (opt-long-name o)
349 :start1 start :end2 len-2)))
350 ((= (length (opt-long-name o)) len-2)
351 (setf matches (list o))
355 (cond ((null matches)
356 (option-parse-error "Unknown option `~A'" optname))
359 #.(concatenate 'string
360 "Ambiguous long option `~A' -- "
364 (mapcar #'opt-long-name matches))))
365 (process-option (car matches)
369 (subseq arg (1+ eqpos)))))))
371 (catch 'option-parse-return
373 (with-simple-restart (skip-option "Skip this bogus option.")
376 ;; We're embroiled in short options: handle them.
378 (if (>= (op-short-opt-index op) (length (op-short-opt op)))
379 (setf (op-short-opt op) nil)
380 (let* ((str (op-short-opt op))
381 (i (op-short-opt-index op))
383 (negp (op-short-opt-neg-p op))
384 (name (format nil "~C~A" (if negp #\+ #\-) ch))
385 (o (find ch (op-options op) :key #'opt-short-name)))
387 (setf (op-short-opt-index op) i)
389 (and negp (not (opt-negated-tag o))))
390 (option-parse-error "Unknown option `~A'" name))
395 (and (< i (length str))
399 (setf (op-short-opt op)
402 ;; End of the list. Say we've finished.
406 ;; Process the next option.
408 (let ((arg (peek-arg)))
411 ;; Non-option. Decide what to do.
412 ((or (<= (length arg) 1)
413 (and (char/= (char arg 0) #\-)
414 (or (char/= (char arg 0) #\+)
415 (not (op-negated-p op)))))
416 (case (op-non-option op)
420 (ret :non-option arg))
422 (funcall (op-non-option op) arg))))
424 ;; Double-hyphen. Stop right now.
429 ;; Numbers. Check these before long options, since `--43'
430 ;; is not a long option.
431 ((and (op-numeric-p op)
432 (or (char= (char arg 0) #\-)
433 (op-negated-numeric-p op))
434 (or (and (digit-char-p (char arg 1))
435 (every #'digit-char-p (subseq arg 2)))
436 (and (or (char= (char arg 1) #\-)
437 (char= (char arg 1) #\+))
439 (digit-char-p (char arg 2))
440 (every #'digit-char-p (subseq arg 3)))))
442 (let ((negp (char= (char arg 0) #\+))
443 (num (parse-integer arg :start 1)))
444 (when (and negp (eq (op-negated-numeric-p op) :-))
448 (op-negated-numeric-p op)
452 (ret (if negp :negated-numeric :numeric) num)))))
454 ;; Long option. Find the matching option-spec and process
456 ((and (char= (char arg 0) #\-)
457 (char= (char arg 1) #\-))
459 (process-long-option arg 2 nil))
461 ;; Short options. All that's left.
464 (let ((negp (char= (char arg 0) #\+))
466 (cond ((and (op-long-only-p op)
467 (not (member ch (op-options op)
468 :key #'opt-short-name)))
469 (process-long-option arg 1 negp))
471 (setf (op-short-opt op) arg
472 (op-short-opt-index op) 1
473 (op-short-opt-neg-p op) negp))))))))))))))
475 (export 'option-parse-try)
476 (defmacro option-parse-try (&body body)
477 "Report errors encountered while parsing options, and try to continue.
479 Also establishes a restart `stop-parsing'. Returns t if parsing completed
480 successfully, or nil if errors occurred."
481 (with-gensyms (retcode)
489 (dolist (rn '(skip-option stop-parsing))
490 (let ((r (find-restart rn)))
491 (when r (invoke-restart r)))))))
494 :report "Give up parsing options."
495 (setf ,retcode nil)))
498 (export 'with-unix-error-reporting)
499 (defmacro with-unix-error-reporting ((&key) &body body)
500 "Evaluate BODY with errors reported in the standard Unix fashion."
504 (simple-condition (,cond)
506 (simple-condition-format-control ,cond)
507 (simple-condition-format-arguments ,cond)))
511 ;;;--------------------------------------------------------------------------
512 ;;; Standard option handlers.
514 (export 'defopthandler)
515 (defmacro defopthandler (name (var &optional (arg (gensym)))
518 "Define an option handler function NAME.
520 Option handlers update a generalized variable, which may be referred to as
521 VAR in the BODY, based on some parameters (the ARGS) and the value of an
522 option-argument named ARG."
523 (let ((func (intern (format nil "OPTHANDLER/~:@(~A~)" name))))
524 (multiple-value-bind (docs decls body) (parse-body body)
526 (setf (get ',name 'opthandler-function) ',func)
527 (defun ,func (,var ,arg ,@args)
529 (declare (ignorable ,arg))
531 (block ,name ,@body)))
535 (defmethod documentation ((symbol symbol) (doc-type (eql 'opthandler)))
536 (let ((func (get symbol 'opthandler-function)))
537 (and func (documentation func 'function))))
538 (defmethod (setf documentation)
539 (string (symbol symbol) (doc-type (eql 'opthandler)))
540 (let ((func (get symbol 'optmacro-function)))
541 (unless func (error "No option handler defined with name `~S'." symbol))
542 (setf (documentation func 'function) string)))
544 (defun parse-c-integer (string &key radix (start 0) end)
545 "Parse (a substring of) STRING according to the standard C rules.
547 Well, almost: the 0 and 0x prefixes are accepted, but so too are
548 0o (Haskell) and 0b (original); also RADIX_DIGITS is accepted, for any
549 radix between 2 and 36. Prefixes are only accepted if RADIX is nil.
550 Returns two values: the integer parsed (or nil if there wasn't enough for
551 a sensible parse), and the index following the characters of the integer."
552 (unless end (setf end (length string)))
553 (labels ((simple (i r goodp sgn)
557 (digit-char-p (char string i) r))
558 (parse-integer string
563 (values (if a (* sgn a) (and goodp 0)) i)))
566 (cond (r (simple i r nil sgn))
567 ((>= i end) (values nil i))
568 ((and (char= (char string i) #\0)
570 (case (char string (1+ i))
571 (#\x (simple (+ i 2) 16 nil sgn))
572 (#\o (simple (+ i 2) 8 nil sgn))
573 (#\b (simple (+ i 2) 2 nil sgn))
574 (t (simple (1+ i) 8 t sgn))))
579 (cond ((not r) (values nil i))
581 (char= (char string i) #\_)
583 (simple (1+ i) r nil sgn))
585 (values (* r sgn) i))))))))
587 (cond ((>= start end) (values nil start))
588 ((char= (char string start) #\-)
589 (get-radix (1+ start) radix -1))
590 ((char= (char string start) #\+)
591 (get-radix (1+ start) radix +1))
593 (get-radix start radix +1)))))
595 (export 'invoke-option-handler)
596 (defun invoke-option-handler (handler loc arg args)
597 "Call an option HANDLER.
599 The handler is invoked to update the locative LOC, given an
600 option-argument ARG, and the remaining ARGS."
601 (apply (if (functionp handler) handler
602 (fdefinition (get handler 'opthandler-function)))
605 ;;;--------------------------------------------------------------------------
606 ;;; Built-in option handlers.
609 (defopthandler set (var) (&optional (value t))
610 "Sets VAR to VALUE; defaults to `t'."
614 (defopthandler clear (var) (&optional (value nil))
615 "Sets VAR to VALUE; defaults to `'nil'."
619 (defopthandler inc (var) (&optional max (step 1))
620 "Increments VAR by STEP (defaults to 1).
622 If MAX is not nil then VAR will not be made larger than MAX. No errors
625 (when (and max (>= var max))
629 (defopthandler dec (var) (&optional min (step 1))
630 "Decrements VAR by STEP (defaults to 1).
632 If MIN is not nil, then VAR will not be made smaller than MIN. No errors
635 (when (and min (<= var min))
639 (defopthandler read (var arg) ()
640 "Stores in VAR the Lisp object found by reading the ARG.
642 Evaluation is forbidden while reading ARG. If there is an error during
643 reading, an error of type option-parse-error is signalled."
645 (let ((*read-eval* nil))
646 (multiple-value-bind (x end) (read-from-string arg t)
647 (unless (>= end (length arg))
648 (option-parse-error "Junk at end of argument `~A'" arg))
651 (option-parse-error (format nil "~A" cond)))))
654 (defopthandler int (var arg) (&key radix min max)
655 "Stores in VAR the integer read from the ARG.
657 Integers are parsed according to C rules, which is normal in Unix; the
658 RADIX may be nil to allow radix prefixes, or an integer between 2 and 36.
659 An option-parse-error is signalled if the ARG is not a valid integer, or
660 if it is not between MIN and MAX (either of which may be nil if no lower
661 or upper bound is wanted)."
662 (multiple-value-bind (v end) (parse-c-integer arg :radix radix)
663 (unless (and v (>= end (length arg)))
664 (option-parse-error "Bad integer `~A'" arg))
665 (when (or (and min (< v min))
668 #.(concatenate 'string
669 "Integer ~A out of range "
670 "(must have ~@[~D <= ~]x~@[ <= ~D~])")
675 (defopthandler string (var arg) ()
676 "Stores ARG in VAR, just as it is."
680 (defopthandler keyword (var arg) (&optional (valid t))
681 "Converts ARG into a keyword.
683 If VALID is t, then any ARG string is acceptable: the argument is
684 uppercased and interned in the keyword package. If VALID is a list, then
685 we ensure that ARG matches one of the elements of the list; unambigious
686 abbreviations are allowed."
689 (setf var (intern (string-upcase arg) :keyword)))
692 (guess (string-upcase arg))
695 (let* ((kn (symbol-name k))
697 (cond ((string= kn guess)
698 (setf matches (list k))
701 (string= guess kn :end2 len))
705 (option-parse-error #.(concatenate 'string
706 "Argument `~A' invalid: "
710 ((null (cdr matches))
711 (setf var (car matches)))
713 (option-parse-error #.(concatenate 'string
714 "Argument `~A' ambiguous: "
720 (defopthandler list (var arg) (&optional handler &rest handler-args)
721 "Collect ARGs in a list at VAR.
723 ARGs are translated by the HANDLER first, if specified. If not, it's as
724 if you asked for `string'."
726 (invoke-option-handler handler (locf arg) arg handler-args))
727 (setf var (nconc var (list arg))))
729 ;;;--------------------------------------------------------------------------
730 ;;; Option descriptions.
732 (export 'defoptmacro)
733 (defmacro defoptmacro (name args &body body)
734 "Defines an option macro NAME.
736 Option macros should produce a list of expressions producing one option
738 (multiple-value-bind (docs decls body) (parse-body body)
740 (setf (get ',name 'optmacro-function)
743 (block ,name ,@body)))
747 (defmethod documentation ((symbol symbol) (doc-type (eql 'optmacro)))
748 (let ((func (get symbol 'optmacro-function)))
749 (and func (documentation func t))))
750 (defmethod (setf documentation)
751 (string (symbol symbol) (doc-type (eql 'optmacro)))
752 (let ((func (get symbol 'optmacro-function)))
753 (unless func (error "No option macro defined with name `~S'." symbol))
754 (setf (documentation func t) string)))
756 (export 'parse-option-form)
757 (eval-when (:compile-toplevel :load-toplevel :execute)
758 (defun parse-option-form (form)
759 "Does the heavy lifting for parsing an option form.
761 See the docstring for the `option' macro for details of the syntax."
763 (cond ((stringp form) form)
764 ((null (cdr form)) (car form))
765 (t `(format nil ,@form))))
769 (stringp (car form))))))
770 (cond ((stringp form)
771 `(%make-option :documentation ,form))
773 (error "option form must be string or list"))
774 ((and (docp (car form)) (null (cdr form)))
775 `(%make-option :documentation ,(doc (car form))))
777 (let (long-name short-name
778 arg-name arg-optional-p
782 (cond ((and (or (not tag) (not negated-tag))
785 (member (car f) '(lambda function)))))
789 ((and (not long-name)
793 (setf long-name (if (stringp f) f
794 (format nil "~(~A~)" f))))
795 ((and (not short-name)
801 ((and (consp f) (symbolp (car f)))
803 (:short-name (setf short-name (cadr f)))
804 (:long-name (setf long-name (cadr f)))
805 (:tag (setf tag (cadr f)))
806 (:negated-tag (setf negated-tag (cadr f)))
807 (:arg (setf arg-name (cadr f)))
808 (:opt-arg (setf arg-name (cadr f))
809 (setf arg-optional-p t))
810 (:doc (setf doc (doc (cdr f))))
811 (t (let ((handler (get (car f)
812 'opthandler-function)))
814 (error "No handler `~S' defined." (car f)))
815 (let* ((var (cadr f))
817 (thunk `#'(lambda (,arg)
818 (,handler (locf ,var)
822 (setf negated-tag thunk)
823 (setf tag thunk)))))))
825 (error "Unexpected thing ~S in option form." f))))
826 `(make-option ,long-name ,short-name ,arg-name
827 ,@(and arg-optional-p `(:arg-optional-p t))
828 ,@(and tag `(:tag ,tag))
829 ,@(and negated-tag `(:negated-tag ,negated-tag))
830 ,@(and doc `(:documentation ,doc)))))))))
833 (defmacro options (&rest optlist)
834 "More convenient way of initializing options. The OPTLIST is a list of
835 OPTFORMS. Each OPTFORM is one of the following:
837 STRING A banner to print.
839 SYMBOL or (SYMBOL STUFF...)
840 If SYMBOL is an optform macro, the result of invoking it.
842 (...) A full option-form. See below.
844 Full option-forms are a list of the following kinds of items.
852 Set the appropriate slot of the option to the given value.
853 The argument is evaluated.
855 (:doc FORMAT-CONTROL ARGUMENTS...)
856 As for (:doc (format nil FORMAT-CONTROL ARGUMENTS...)).
858 KEYWORD, (function ...), (lambda ...)
859 If no TAG is set yet, then as a TAG; otherwise as the
862 STRING (or SYMBOL or RATIONAL)
863 If no LONG-NAME seen yet, then the LONG-NAME. For symbols
864 and rationals, the item is converted to a string and squashed
867 CHARACTER If no SHORT-NAME, then the SHORT-NAME.
869 STRING or (STRING STUFF...)
870 If no DOCUMENTATION set yet, then the DOCUMENTATION string,
871 as for (:doc STRING STUFF...)
874 Set the ARG-NAME, and also set ARG-OPTIONAL-P.
876 (HANDLER VAR ARGS...)
877 If no TAG is set yet, attach the HANDLER to this option,
878 giving it ARGS. Otherwise, set the NEGATED-TAG."
880 `(list ,@(mapcan (lambda (form)
883 (cond ((symbolp form) (values form nil))
884 ((and (consp form) (symbolp (car form)))
885 (values (car form) (cdr form)))
886 (t (values nil nil)))
887 (let ((macro (and sym (get sym 'optmacro-function))))
890 (list (parse-option-form form))))))
893 ;;;--------------------------------------------------------------------------
894 ;;; Support stuff for help and usage messages.
896 (locally (declare #+sbcl (sb-ext:muffle-conditions style-warning))
897 (defun print-text (string
898 &optional (stream *standard-output*)
899 &key (start 0) (end nil))
900 "Prints and line-breaks STRING to a pretty-printed STREAM.
902 The string is broken at whitespace and newlines in the obvious way.
903 Stuff between square brackets is not broken: this makes usage messages
909 (write-string string stream :start start :end i)
911 (unless end (setf end (length string)))
916 (let ((ch (char string i)))
917 (cond ((char= ch #\newline)
920 (pprint-newline :mandatory stream))
921 ((whitespace-char-p ch)
927 (pprint-newline :fill stream))
931 (#\] (when (plusp nest) (decf nest))))))
934 (export 'simple-usage)
935 (defun simple-usage (opts &optional mandatory-args)
936 "Build a simple usage list.
938 The usage list is constructed from a list OPTS of `option' values, and
939 a list MANDATORY-ARGS of mandatory argument names; the latter defaults to
941 (let (short-simple long-simple short-arg long-arg)
943 (cond ((not (and (opt-documentation o)
945 ((and (opt-short-name o) (opt-arg-name o))
948 (push o short-simple))
952 (push o long-simple))))
954 (nconc (and short-simple
955 (list (format nil "[-~{~C~}]"
956 (sort (mapcar #'opt-short-name short-simple)
960 (format nil "[--~A]" (opt-long-name o)))
961 (sort long-simple #'string< :key #'opt-long-name)))
964 (format nil "~:[[-~C ~A]~;[-~C[~A]]~]"
965 (opt-arg-optional-p o)
968 (sort short-arg #'char-lessp
969 :key #'opt-short-name)))
972 (format nil "~:[[--~A ~A]~;[--~A[=~A]]~]"
973 (opt-arg-optional-p o)
976 (sort long-arg #'string-lessp
977 :key #'opt-long-name)))
978 (if (listp mandatory-args)
980 (list mandatory-args))))))
983 (defun show-usage (prog usage &optional (stream *standard-output*))
984 "Basic usage-showing function.
986 PROG is the program name, probably from `*program-name*'. USAGE is a list
987 of possible usages of the program, each of which is a list of items to be
988 supplied by the user. In simple cases, a single string is sufficient."
989 (pprint-logical-block (stream nil :prefix "Usage: ")
990 (dolist (u (if (listp usage) usage (list usage)))
991 (pprint-logical-block (stream nil
992 :prefix (concatenate 'string prog " "))
993 (format stream "~{~A~^ ~:_~}" (if (listp u) u (list u))))))
996 (defun show-options-help (opts &optional (stream *standard-output*))
997 "Write help for OPTS to the STREAM.
999 This is the core of the `show-help' function."
1002 (let ((doc (opt-documentation o)))
1004 ((not (or (opt-short-name o)
1008 (setf newlinep nil))
1009 (pprint-logical-block (stream nil)
1010 (print-text doc stream))
1014 (pprint-logical-block (stream nil :prefix " ")
1015 (format stream "~:[ ~;-~:*~C~:[~;,~]~:*~]~@[ --~A~]"
1018 (when (opt-arg-name o)
1020 "~:[~;[~]~:[~0@*~:[ ~;~]~*~;=~]~A~0@*~:[~;]~]"
1021 (opt-arg-optional-p o)
1024 (write-string " " stream)
1025 (pprint-tab :line 30 1 stream)
1026 (pprint-indent :block 30 stream)
1027 (print-text doc stream))
1028 (terpri stream)))))))
1031 (defun show-help (prog ver usage opts &optional (stream *standard-output*))
1032 "Basic help-showing function.
1034 PROG is the program name, probably from `*program-name*'. VER is the
1035 program's version number. USAGE is a list of the possible usages of the
1036 program, each of which may be a list of items to be supplied. OPTS is the
1037 list of supported options, as provided to the options parser. STREAM is
1038 the stream to write on."
1039 (format stream "~A, version ~A~2%" prog ver)
1040 (show-usage prog usage stream)
1042 (show-options-help opts stream))
1044 (export 'sanity-check-option-list)
1045 (defun sanity-check-option-list (opts)
1046 "Check the option list OPTS for basic sanity.
1048 Reused short and long option names are diagnosed. Maybe other problems
1049 will be reported later. Returns a list of warning strings."
1050 (let ((problems nil)
1051 (longs (make-hash-table :test #'equal))
1052 (shorts (make-hash-table)))
1053 (flet ((problem (msg &rest args)
1054 (push (apply #'format nil msg args) problems)))
1056 (push o (gethash (opt-long-name o) longs))
1057 (push o (gethash (opt-short-name o) shorts)))
1058 (maphash (lambda (k v)
1059 (when (and k (cdr v))
1060 (problem "Long name `--~A' reused in ~S" k v)))
1062 (maphash (lambda (k v)
1063 (when (and k (cdr v))
1064 (problem "Short name `-~C' reused in ~S" k v)))
1068 ;;;--------------------------------------------------------------------------
1069 ;;; Full program descriptions.
1071 (export '(*help* *version* *usage*))
1072 (defvar *help* nil "Help text describing the program.")
1073 (defvar *version* "<unreleased>" "The program's version number.")
1074 (defvar *usage* nil "A usage summary string")
1077 (defun do-usage (&optional (stream *standard-output*))
1078 (show-usage *program-name* *usage* stream))
1082 (do-usage *error-output*)
1085 (defun opt-help (arg)
1086 (declare (ignore arg))
1087 (show-help *program-name* *version* *usage* *options*)
1089 (string (terpri) (write-string *help*))
1091 ((or function symbol) (terpri) (funcall *help*)))
1094 (defun opt-version (arg)
1095 (declare (ignore arg))
1096 (format t "~A, version ~A~%" *program-name* *version*)
1098 (defun opt-usage (arg)
1099 (declare (ignore arg))
1103 (export 'help-options)
1104 (defoptmacro help-options (&key (short-help #\h)
1107 "Inserts a standard help options collection in an options list."
1108 (flet ((shortform (char)
1109 (and char (list char))))
1113 (,@(shortform short-help) "help" #'opt-help
1114 "Show this help message.")
1115 (,@(shortform short-version) "version" #'opt-version
1116 ("Show ~A's version number." *program-name*))
1117 (,@(shortform short-usage) "usage" #'opt-usage
1118 ("Show a very brief usage summary for ~A." *program-name*))))))
1120 (export 'define-program)
1121 (defun define-program (&key
1122 (program-name nil progp)
1124 (version nil versionp)
1126 (full-usage nil fullp)
1127 (options nil optsp))
1128 "Sets up all the required things a program needs to have to parse options
1129 and respond to them properly."
1130 (when progp (setf *program-name* program-name))
1131 (when helpp (setf *help* help))
1132 (when versionp (setf *version* version))
1133 (when optsp (setf *options* options))
1134 (cond ((and usagep fullp) (error "conflicting options"))
1135 (usagep (setf *usage* (simple-usage *options* usage)))
1136 (fullp (setf *usage* full-usage))))
1138 (export 'do-options)
1139 (defmacro do-options ((&key (parser '(make-option-parser)))
1141 "Handy all-in-one options parser macro.
1143 PARSER defaults to a new options parser using the preset default options
1144 structure. The CLAUSES are `case2'-like clauses to match options, and
1145 must be exhaustive. If there is a clause (nil (REST) FORMS...) then the
1146 FORMS are evaluated after parsing is done with REST bound to the remaining
1147 command-line arguments."
1151 (,(if (find t clauses :key #'car) 'case2 'ecase2)
1152 (option-parse-next ,parser)
1154 ,@(remove-if #'null clauses :key #'car)))
1155 ,@(let ((tail (find nil clauses :key #'car)))
1157 (destructuring-bind ((&optional arg) &rest forms) (cdr tail)
1159 (list `(let ((,arg (option-parse-remainder ,parser)))
1163 ;;;----- That's all, folks --------------------------------------------------