Fix VARSYMP for empty symbol names.
[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 ;;;; ** Anaphoric conditionals
59
60 (defmacro if-bind (var test &body then/else)
61   "Anaphoric IF control structure.
62
63 VAR (a symbol) will be bound to the primary value of TEST. If
64 TEST returns a true value then THEN will be executed, otherwise
65 ELSE will be executed."
66   (assert (first then/else)
67           (then/else)
68           "IF-BIND missing THEN clause.")
69   (destructuring-bind (then &optional else)
70       then/else
71     `(let ((,var ,test))
72        (if ,var ,then ,else))))
73
74 (defmacro aif (test then &optional else)
75   "Just like IF-BIND but the var is always IT."
76   `(if-bind it ,test ,then ,else))
77
78 ;;;; ** Simple list matching based on code from Paul Graham's On Lisp.
79
80 (defmacro acond2 (&rest clauses)
81   (if (null clauses)
82       nil
83       (with-gensyms (val foundp)
84         (destructuring-bind ((test &rest progn) &rest others)
85             clauses
86           `(multiple-value-bind (,val ,foundp)
87                ,test
88              (if (or ,val ,foundp)
89                  (let ((it ,val))
90                    (declare (ignorable it))
91                    ,@progn)
92                  (acond2 ,@others)))))))
93
94 (defun varsymp (x)
95   (and (symbolp x)
96        (let ((name (symbol-name x)))
97          (and (>= (length name) 2)
98               (char= (char name 0) #\?)))))
99
100 (defun binding (x binds)
101   (labels ((recbind (x binds)
102              (aif (assoc x binds)
103                   (or (recbind (cdr it) binds)
104                       it))))
105     (let ((b (recbind x binds)))
106       (values (cdr b) b))))
107
108 (defun list-match (x y &optional binds)
109   (acond2
110     ((or (eql x y) (eql x '_) (eql y '_))
111      (values binds t))
112     ((binding x binds) (list-match it y binds))
113     ((binding y binds) (list-match x it binds))
114     ((varsymp x) (values (cons (cons x y) binds) t))
115     ((varsymp y) (values (cons (cons y x) binds) t))
116     ((and (consp x) (consp y) (list-match (car x) (car y) binds))
117      (list-match (cdr x) (cdr y) it))
118     (t (values nil nil))))
119
120 (defun vars (match-spec)
121   (let ((vars nil))
122     (labels ((find-vars (spec)
123                (cond
124                  ((null spec) nil)
125                  ((varsymp spec) (push spec vars))
126                  ((consp spec)
127                   (find-vars (car spec))
128                   (find-vars (cdr spec))))))
129       (find-vars match-spec))
130     (delete-duplicates vars)))
131
132 (defmacro list-match-case (target &body clauses)
133   (if clauses
134       (destructuring-bind ((test &rest progn) &rest others)
135           clauses
136         (with-gensyms (tgt binds success)
137           `(let ((,tgt ,target))
138              (multiple-value-bind (,binds ,success)
139                  (list-match ,tgt ',test)
140                (declare (ignorable ,binds))
141                (if ,success
142                    (let ,(mapcar (lambda (var)
143                                    `(,var (cdr (assoc ',var ,binds))))
144                                  (vars test))
145                      (declare (ignorable ,@(vars test)))
146                      ,@progn)
147                    (list-match-case ,tgt ,@others))))))
148       nil))
149
150 ;;;; * def-special-environment
151
152 (defun check-required (name vars required)
153   (dolist (var required)
154     (assert (member var vars)
155             (var)
156             "Unrecognized symbol ~S in ~S." var name)))
157
158 (defmacro def-special-environment (name (&key accessor binder binder*)
159                                   &rest vars)
160   "Define two macros for dealing with groups or related special variables.
161
162 ACCESSOR is defined as a macro: (defmacro ACCESSOR (VARS &rest
163 BODY)).  Each element of VARS will be bound to the
164 current (dynamic) value of the special variable.
165
166 BINDER is defined as a macro for introducing (and binding new)
167 special variables. It is basically a readable LET form with the
168 prorpe declarations appended to the body. The first argument to
169 BINDER must be a form suitable as the first argument to LET.
170
171 ACCESSOR defaults to a new symbol in the same package as NAME
172 which is the concatenation of \"WITH-\" NAME. BINDER is built as
173 \"BIND-\" and BINDER* is BINDER \"*\"."
174   (unless accessor
175     (setf accessor (format-symbol (symbol-package name) "~A-~A" '#:with name)))
176   (unless binder
177     (setf binder   (format-symbol (symbol-package name) "~A-~A" '#:bind name)))
178   (unless binder*
179     (setf binder*  (format-symbol (symbol-package binder) "~A~A" binder '#:*)))
180   `(eval-when (:compile-toplevel :load-toplevel :execute)
181      (flet ()
182        (defmacro ,binder (requested-vars &body body)
183          (check-required ',name ',vars (mapcar #'car requested-vars))
184          `(let ,requested-vars
185             (declare (special ,@(mapcar #'car requested-vars)))
186             ,@body))
187        (defmacro ,binder* (requested-vars &body body)
188          (check-required ',name ',vars (mapcar #'car requested-vars))
189          `(let* ,requested-vars
190             (declare (special ,@(mapcar #'car requested-vars)))
191             ,@body))
192        (defmacro ,accessor (requested-vars &body body)
193          (check-required ',name ',vars requested-vars)
194          `(locally (declare (special ,@requested-vars))
195             ,@body))
196        ',name)))
197
198 ;; Copyright (c) 2002-2006, Edward Marco Baringer
199 ;; All rights reserved.
200 ;;
201 ;; Redistribution and use in source and binary forms, with or without
202 ;; modification, are permitted provided that the following conditions are
203 ;; met:
204 ;;
205 ;;  - Redistributions of source code must retain the above copyright
206 ;;    notice, this list of conditions and the following disclaimer.
207 ;;
208 ;;  - Redistributions in binary form must reproduce the above copyright
209 ;;    notice, this list of conditions and the following disclaimer in the
210 ;;    documentation and/or other materials provided with the distribution.
211 ;;
212 ;;  - Neither the name of Edward Marco Baringer, nor BESE, nor the names
213 ;;    of its contributors may be used to endorse or promote products
214 ;;    derived from this software without specific prior written permission.
215 ;;
216 ;; THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
217 ;; "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
218 ;; LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR
219 ;; A PARTICULAR PURPOSE ARE DISCLAIMED.  IN NO EVENT SHALL THE COPYRIGHT
220 ;; OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL,
221 ;; SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT
222 ;; LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE,
223 ;; DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY
224 ;; THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT
225 ;; (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE
226 ;; OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE