Shut up warnings about unknown *SUITE* variable.
[fiveam.git] / src / utils.lisp
1 ;;;; -*- Mode: Lisp; indent-tabs-mode: nil -*-
2
3 (in-package :it.bese.fiveam)
4
5 (defmacro dolist* ((iterator list &optional return-value) &body body)
6   "Like DOLIST but destructuring-binds the elements of LIST.
7
8 If ITERATOR is a symbol then dolist* is just like dolist EXCEPT
9 that it creates a fresh binding."
10   (if (listp iterator)
11       (let ((i (gensym "DOLIST*-I-")))
12         `(dolist (,i ,list ,return-value)
13            (destructuring-bind ,iterator ,i
14              ,@body)))
15       `(dolist (,iterator ,list ,return-value)
16          (let ((,iterator ,iterator))
17            ,@body))))
18
19 (defun make-collector (&optional initial-value)
20   "Create a collector function.
21
22 A Collector function will collect, into a list, all the values
23 passed to it in the order in which they were passed. If the
24 callector function is called without arguments it returns the
25 current list of values."
26   (let ((value initial-value)
27         (cdr (last initial-value)))
28     (lambda (&rest items)
29       (if items
30           (progn
31             (if value
32                 (if cdr
33                     (setf (cdr cdr) items
34                           cdr (last items))
35                     (setf cdr (last items)))
36                 (setf value items
37                       cdr (last items)))
38             items)
39           value))))
40
41 (defun partitionx (list &rest lambdas)
42   (let ((collectors (mapcar (lambda (l)
43                               (cons (if (and (symbolp l)
44                                              (member l (list :otherwise t)
45                                                      :test #'string=))
46                                         (constantly t)
47                                         l)
48                                     (make-collector)))
49                             lambdas)))
50     (dolist (item list)
51       (block item
52         (dolist* ((test-func . collector-func) collectors)
53           (when (funcall test-func item)
54             (funcall collector-func item)
55             (return-from item)))))
56     (mapcar #'funcall (mapcar #'cdr collectors))))
57
58 ;;;; ** Simple list matching based on code from Paul Graham's On Lisp.
59
60 (defmacro acond2 (&rest clauses)
61   (if (null clauses)
62       nil
63       (with-gensyms (val foundp)
64         (destructuring-bind ((test &rest progn) &rest others)
65             clauses
66           `(multiple-value-bind (,val ,foundp)
67                ,test
68              (if (or ,val ,foundp)
69                  (let ((it ,val))
70                    (declare (ignorable it))
71                    ,@progn)
72                  (acond2 ,@others)))))))
73
74 (defun varsymp (x)
75   (and (symbolp x) (eq (aref (symbol-name x) 0) #\?)))
76
77 (defun binding (x binds)
78   (labels ((recbind (x binds)
79              (if-let (value (assoc x binds))
80                (or (recbind (cdr value) binds)
81                    value))))
82     (let ((b (recbind x binds)))
83       (values (cdr b) b))))
84
85 (defun list-match (x y &optional binds)
86   (acond2
87     ((or (eql x y) (eql x '_) (eql y '_))
88      (values binds t))
89     ((binding x binds) (list-match it y binds))
90     ((binding y binds) (list-match x it binds))
91     ((varsymp x) (values (cons (cons x y) binds) t))
92     ((varsymp y) (values (cons (cons y x) binds) t))
93     ((and (consp x) (consp y) (list-match (car x) (car y) binds))
94      (list-match (cdr x) (cdr y) it))
95     (t (values nil nil))))
96
97 (defun vars (match-spec)
98   (let ((vars nil))
99     (labels ((find-vars (spec)
100                (cond
101                  ((null spec) nil)
102                  ((varsymp spec) (push spec vars))
103                  ((consp spec)
104                   (find-vars (car spec))
105                   (find-vars (cdr spec))))))
106       (find-vars match-spec))
107     (delete-duplicates vars)))
108
109 (defmacro list-match-case (target &body clauses)
110   (if clauses
111       (destructuring-bind ((test &rest progn) &rest others)
112           clauses
113         (with-gensyms (tgt binds success)
114           `(let ((,tgt ,target))
115              (multiple-value-bind (,binds ,success)
116                  (list-match ,tgt ',test)
117                (declare (ignorable ,binds))
118                (if ,success
119                    (let ,(mapcar (lambda (var)
120                                    `(,var (cdr (assoc ',var ,binds))))
121                                  (vars test))
122                      (declare (ignorable ,@(vars test)))
123                      ,@progn)
124                    (list-match-case ,tgt ,@others))))))
125       nil))
126
127 ;;;; * def-special-environment
128
129 (defun check-required (name vars required)
130   (dolist (var required)
131     (assert (member var vars)
132             (var)
133             "Unrecognized symbol ~S in ~S." var name)))
134
135 (defmacro def-special-environment (name (&key accessor binder binder*)
136                                   &rest vars)
137   "Define two macros for dealing with groups or related special variables.
138
139 ACCESSOR is defined as a macro: (defmacro ACCESSOR (VARS &rest
140 BODY)).  Each element of VARS will be bound to the
141 current (dynamic) value of the special variable.
142
143 BINDER is defined as a macro for introducing (and binding new)
144 special variables. It is basically a readable LET form with the
145 prorpe declarations appended to the body. The first argument to
146 BINDER must be a form suitable as the first argument to LET.
147
148 ACCESSOR defaults to a new symbol in the same package as NAME
149 which is the concatenation of \"WITH-\" NAME. BINDER is built as
150 \"BIND-\" and BINDER* is BINDER \"*\"."
151   (unless accessor
152     (setf accessor (format-symbol (symbol-package name) "~A-~A" '#:with name)))
153   (unless binder
154     (setf binder   (format-symbol (symbol-package name) "~A-~A" '#:bind name)))
155   (unless binder*
156     (setf binder*  (format-symbol (symbol-package binder) "~A~A" binder '#:*)))
157   `(eval-when (:compile-toplevel :load-toplevel :execute)
158      (flet ()
159        (defmacro ,binder (requested-vars &body body)
160          (check-required ',name ',vars (mapcar #'car requested-vars))
161          `(let ,requested-vars
162             (declare (special ,@(mapcar #'car requested-vars)))
163             ,@body))
164        (defmacro ,binder* (requested-vars &body body)
165          (check-required ',name ',vars (mapcar #'car requested-vars))
166          `(let* ,requested-vars
167             (declare (special ,@(mapcar #'car requested-vars)))
168             ,@body))
169        (defmacro ,accessor (requested-vars &body body)
170          (check-required ',name ',vars requested-vars)
171          `(locally (declare (special ,@requested-vars))
172             ,@body))
173        ',name)))
174
175 ;; Copyright (c) 2002-2006, Edward Marco Baringer
176 ;; All rights reserved.
177 ;;
178 ;; Redistribution and use in source and binary forms, with or without
179 ;; modification, are permitted provided that the following conditions are
180 ;; met:
181 ;;
182 ;;  - Redistributions of source code must retain the above copyright
183 ;;    notice, this list of conditions and the following disclaimer.
184 ;;
185 ;;  - Redistributions in binary form must reproduce the above copyright
186 ;;    notice, this list of conditions and the following disclaimer in the
187 ;;    documentation and/or other materials provided with the distribution.
188 ;;
189 ;;  - Neither the name of Edward Marco Baringer, nor BESE, nor the names
190 ;;    of its contributors may be used to endorse or promote products
191 ;;    derived from this software without specific prior written permission.
192 ;;
193 ;; THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
194 ;; "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
195 ;; LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR
196 ;; A PARTICULAR PURPOSE ARE DISCLAIMED.  IN NO EVENT SHALL THE COPYRIGHT
197 ;; OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL,
198 ;; SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT
199 ;; LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE,
200 ;; DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY
201 ;; THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT
202 ;; (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE
203 ;; OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE