]> asedeno.scripts.mit.edu Git - cl-protobufs.git/blob - utilities.lisp
While implementing the Fortuneteller stubby server, I ran into
[cl-protobufs.git] / utilities.lisp
1 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
2 ;;;                                                                  ;;;
3 ;;; Confidential and proprietary information of ITA Software, Inc.   ;;;
4 ;;;                                                                  ;;;
5 ;;; Copyright (c) 2012 ITA Software, Inc.  All rights reserved.      ;;;
6 ;;;                                                                  ;;;
7 ;;; Original author: Scott McKay                                     ;;;
8 ;;;                                                                  ;;;
9 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
10
11 (in-package "PROTO-IMPL")
12
13
14 ;;; Optimized fixnum arithmetic
15
16 (eval-when (:compile-toplevel :load-toplevel :execute)
17
18 (defparameter $optimize-default     '(optimize (speed 1) (safety 3) (debug 3))
19   "Compiler optimization settings for safe, debuggable code.")
20 (defparameter $optimize-fast-unsafe '(optimize (speed 3) (safety 0) (debug 0))
21   "Compiler optimization settings for fast, unsafe, hard-to-debug code.")
22
23 )       ;eval-when
24
25
26 (defmacro i+ (&rest fixnums)
27   `(the fixnum (+ ,@(loop for n in fixnums collect `(the fixnum ,n)))))
28
29 (defmacro i- (number &rest fixnums)
30   `(the fixnum (- (the fixnum ,number) ,@(loop for n in fixnums collect `(the fixnum ,n)))))
31
32 (defmacro i* (&rest fixnums)
33   `(the fixnum (* ,@(loop for n in fixnums collect `(the fixnum ,n)))))
34
35 (defmacro i= (&rest fixnums)
36   `(= ,@(loop for n in fixnums collect `(the fixnum ,n))))
37
38 (defmacro i< (&rest fixnums)
39   `(< ,@(loop for n in fixnums collect `(the fixnum ,n))))
40
41 (defmacro i<= (&rest fixnums)
42   `(<= ,@(loop for n in fixnums collect `(the fixnum ,n))))
43
44 (defmacro i> (&rest fixnums)
45   `(> ,@(loop for n in fixnums collect `(the fixnum ,n))))
46
47 (defmacro i>= (&rest fixnums)
48   `(>= ,@(loop for n in fixnums collect `(the fixnum ,n))))
49
50 (defmacro iash (value count)
51   `(the fixnum (ash (the fixnum ,value) (the fixnum ,count))))
52
53 (defmacro ilogior (&rest fixnums)
54   (if (cdr fixnums)
55     `(the fixnum (logior (the fixnum ,(car fixnums))
56                          ,(if (cddr fixnums)
57                             `(ilogior ,@(cdr fixnums))
58                             `(the fixnum ,(cadr fixnums)))))
59     `(the fixnum ,(car fixnums))))
60
61 (defmacro ilogand (&rest fixnums)
62   (if (cdr fixnums)
63     `(the fixnum (logand (the fixnum ,(car fixnums))
64                          ,(if (cddr fixnums)
65                             `(ilogand ,@(cdr fixnums))
66                             `(the fixnum ,(cadr fixnums)))))
67     `(the fixnum ,(car fixnums))))
68
69 (define-modify-macro iincf (&optional (delta 1)) i+)
70 (define-modify-macro idecf (&optional (delta 1)) i-)
71
72 (defmacro ildb (bytespec value)
73   `(the fixnum (ldb ,bytespec (the fixnum ,value))))
74
75
76 ;;; String utilities
77
78 (defun starts-with (string prefix &key (start 0))
79   "Returns true if 'string' starts with the prefix 'prefix' (case insensitive)."
80   (and (i>= (length string) (i+ start (length prefix)))
81        (string-equal string prefix :start1 start :end1 (i+ start (length prefix)))
82        prefix))
83
84 (defun ends-with (string suffix &key (end (length string)))
85   "Returns true if 'string' ends with the prefix 'prefix' (case insensitive)."
86   (and (i>= end (length suffix))
87        (string-equal string suffix :start1 (i- end (length suffix)) :end1 end)
88        suffix))
89
90
91 ;; (camel-case "camel-case") => "CamelCase"
92 (defun camel-case (string &optional (separators '(#\-)))
93   (let ((words (split-string string :separators separators)))
94     (format nil "~{~@(~A~)~}" words)))
95
96 ;; (camel-case-but-one "camel-case") => "camelCase"
97 (defun camel-case-but-one (string &optional (separators '(#\-)))
98   (let ((words (split-string string :separators separators)))
99     (format nil "~(~A~)~{~@(~A~)~}" (car words) (cdr words))))
100
101
102 ;; (uncamel-case "CamelCase") => "CAMEL-CASE"
103 ;; (uncamel-case "TCPConnection") => "TCP-CONNECTION"
104 ;; (uncamel-case "NewTCPConnection") => "NEW-TCP-CONNECTION"
105 ;; (uncamel-case "new_RPC_LispService") => "NEW-RPC-LISP-SERVICE"
106 ;; (uncamel-case "RPC_LispServiceRequest_get_request") => "RPC-LISP-SERVICE-REQUEST-GET-REQUEST"
107 ;; (uncamel-case "TCP2Name3") => "TCP2-NAME3"
108 (defun uncamel-case (name)
109   ;; We need a whole state machine to get this right
110   (labels ((uncamel (chars state result)
111              (let ((ch (first chars)))
112                (cond ((null chars)
113                       result)
114                      ((upper-case-p ch)
115                       (uncamel (rest chars) 'upper
116                                (case state
117                                  ((upper)
118                                   ;; "TCPConnection" => "TCP-CONNECTION"
119                                   (if (and (second chars) (lower-case-p (second chars)))
120                                     (list* ch #\- result)
121                                     (cons ch result)))
122                                  ((lower digit) (list* ch #\- result))
123                                  (otherwise (cons ch result)))))
124                      ((lower-case-p ch)
125                       (uncamel (rest chars) 'lower
126                                (cons (char-upcase ch) result)))
127                      ((digit-char-p ch)
128                       (uncamel (rest chars) 'digit 
129                                (cons ch result)))
130                      ((or (eql ch #\-) (eql ch #\_))
131                       (uncamel (rest chars) 'dash
132                                (cons #\- result)))
133                      ((eql ch #\.)
134                       (uncamel (rest chars) 'dot
135                                (cons #\. result)))
136                      (t
137                       (error "Invalid name character: ~A" ch))))))
138     (concatenate 'string (nreverse (uncamel (concatenate 'list name) nil ())))))
139
140
141 (defun split-string (line &key (start 0) (end (length line)) (separators '(#\-)))
142   "Given a string 'string', splits it at each of the separators.
143    Returns a list of the string pieces, with empty pieces removed."
144   (unless (i= start end)
145     (loop for this fixnum = start then (i+ next 1)
146           for next fixnum = (or (position-if #'(lambda (ch) (member ch separators)) line
147                                              :start this :end end)
148                                 end)
149           for piece = (string-right-trim '(#\space) (subseq line this next))
150           when (not (i= (length piece) 0))
151             collect piece
152           until (i>= next end))))
153
154
155 ;;; Managing symbols
156
157 (defmacro with-gensyms ((&rest bindings) &body body)
158   `(let ,(mapcar #'(lambda (b) `(,b (gensym ,(string b)))) bindings)
159      ,@body))
160
161 (defun make-lisp-symbol (string)
162   "Intern a string of the 'package:string' and return the symbol."
163   (let* ((string (string string))
164          (colon  (position #\: string))
165          (pkg    (if colon (subseq string 0 colon) "KEYWORD"))
166          (sym    (if colon (subseq string (+ colon 1)) string)))
167     (intern sym pkg)))
168
169 (defun fintern (format-string &rest format-args)
170   "Interns a new symbol in the current package."
171   (declare (dynamic-extent format-args))
172   (intern (nstring-upcase (apply #'format nil format-string format-args))))
173
174 (defun kintern (format-string &rest format-args)
175   "Interns a new symbol in the keyword package."
176   (declare (dynamic-extent format-args))
177   (intern (nstring-upcase (apply #'format nil format-string format-args)) "KEYWORD"))
178
179 (defun keywordify (x)
180   "Given a symbol designator 'x', return a keyword whose name is 'x'.
181    If 'x' is nil, this returns nil."
182   (check-type x (or string symbol null))
183   (cond ((null x) nil)
184         ((keywordp x) x)
185         ((symbolp x) (keywordify (symbol-name x)))
186         ((zerop (length x)) nil)
187         ((string-not-equal x "nil")
188          (intern (string-upcase x) (find-package "KEYWORD")))
189         (t nil)))
190
191
192 ;;; Collectors, etc
193
194 (defmacro with-collectors ((&rest collection-descriptions) &body body)
195   (let ((let-bindings  ())
196         (flet-bindings ())
197         (dynamic-extents ())
198         (vobj '#:OBJECT))
199     (dolist (description collection-descriptions)
200       (destructuring-bind (place name) description
201         (let ((vtail (make-symbol (format nil "~A-TAIL" place))))
202           (setq dynamic-extents
203                 (nconc dynamic-extents `(#',name)))
204           (setq let-bindings
205                 (nconc let-bindings
206                        `((,place ())
207                          (,vtail nil))))
208           (setq flet-bindings
209                 (nconc flet-bindings
210                        `((,name (,vobj)
211                            (setq ,vtail (if ,vtail
212                                           (setf (cdr ,vtail)  (list ,vobj))
213                                           (setf ,place (list ,vobj)))))))))))
214     `(let (,@let-bindings)
215        (flet (,@flet-bindings)
216          ,@(and dynamic-extents
217                 `((declare (dynamic-extent ,@dynamic-extents))))
218          ,@body))))
219
220 (defmacro with-prefixed-accessors (names (prefix object) &body body)
221   `(with-accessors (,@(loop for name in names
222                             collect `(,name ,(fintern "~A~A" prefix name))))
223        ,object
224      ,@body))
225
226 (defmacro dovector ((var vector &optional value) &body body)
227   (with-gensyms (vidx vlen vvec)
228     `(let* ((,vvec ,vector)
229             (,vlen (length ,vvec)))
230        (loop for ,vidx fixnum from 0 below ,vlen
231              as ,var = (aref ,vvec ,vidx)
232              do (progn ,@body)
233              finally (return ,value)))))
234
235
236 ;;; Functional programming, please
237
238 (defun curry (function &rest args)
239   (if (and args (null (cdr args)))                      ;fast test for length = 1
240     (let ((arg (car args)))
241       #'(lambda (&rest more-args)
242           (apply function arg more-args)))
243     #'(lambda (&rest more-args)
244         (apply function (append args more-args)))))
245
246 (define-compiler-macro curry (&whole form function &rest args &environment env)
247   (declare (ignore env))
248   (if (and (listp function)
249            (eq (first function) 'function)
250            (symbolp (second function))
251            (and args (null (cdr args))))
252     `#'(lambda (&rest more-args)
253          (apply ,function ,(car args) more-args))
254     form))
255
256
257 ;;; Types
258
259 ;; A parameterized list type for repeated fields
260 ;; The elements aren't type-checked
261 (deftype list-of (type)
262   (if (eq type 'null)
263     'null
264     'list))
265
266 ;; The same, but use a (stretchy) vector
267 (deftype vector-of (type)
268   (if (eq type 'null)
269     'null
270     '(array * (*))))            ;an 1-dimensional array of any type
271
272 ;; This corresponds to the :bytes Protobufs type
273 (deftype byte-vector () '(array (unsigned-byte 8) (*)))
274
275 (defun make-byte-vector (size)
276   (make-array size :element-type '(unsigned-byte 8)))
277
278 ;; The Protobufs integer types
279 (deftype    int32 () '(signed-byte 32))
280 (deftype    int64 () '(signed-byte 64))
281 (deftype   uint32 () '(unsigned-byte 32))
282 (deftype   uint64 () '(unsigned-byte 64))
283 (deftype   sint32 () '(signed-byte 32))
284 (deftype   sint64 () '(signed-byte 64))
285 (deftype  fixed32 () '(signed-byte 32))
286 (deftype  fixed64 () '(signed-byte 64))
287 (deftype sfixed32 () '(signed-byte 32))
288 (deftype sfixed64 () '(signed-byte 64))
289
290
291 ;;; Code generation utilities
292
293 (defvar *proto-name-separators* '(#\- #\_ #\/ #\space))
294 (defvar *camel-case-field-names* nil)
295
296 (defun find-proto-package (name)
297   "A very fuzzy definition of 'find-package'."
298   (typecase name
299     ((or string symbol)
300      ;; Try looking under the given name and the all-uppercase name
301      (or (find-package (string name))
302          (find-package (string-upcase (string name)))))
303     ((cons)
304      ;; If 'name' is a list, it's actually a fully-qualified path
305      (or (find-proto-package (first name))
306          (find-proto-package (format nil "~{~A~^.~}" name))))))
307
308 ;; "class-name" -> "ClassName", ("ClassName")
309 ;; "outer-class.inner-class" -> "InnerClass", ("OuterClass" "InnerClass")
310 (defun class-name->proto (x)
311   "Given a Lisp class name, returns a Protobufs message or enum name.
312    The second value is the fully qualified name, as a list."
313   (let* ((xs (split-string (string x) :separators '(#\.)))
314          (ns (loop for x in (butlast xs)
315                    collect (remove-if-not #'alphanumericp
316                                           (camel-case (format nil "~A" x) *proto-name-separators*))))
317          (nx (car (last xs)))
318          (name (remove-if-not #'alphanumericp (camel-case nx *proto-name-separators*))))
319     (values name (append ns (list name))
320             ;; This might be the name of a package, too
321             (format nil "~{~A~^.~}" (butlast xs)))))
322
323 ;; "enum-value" -> "ENUM_VALUE", ("ENUM_VALUE")
324 ;; "class-name.enum-value" -> "ENUM_VALUE", ("ClassName" "ENUM_VALUE")
325 (defun enum-name->proto (x &optional prefix)
326   "Given a Lisp enum value name, returns a Protobufs enum value name.
327    The second value is the fully qualified name, as a list."
328   (let* ((xs (split-string (string x) :separators '(#\.)))
329          (ns (loop for x in (butlast xs)
330                    collect (remove-if-not #'alphanumericp
331                                           (camel-case (format nil "~A" x) *proto-name-separators*))))
332          (nx (string-upcase (car (last xs))))
333          (nx (if (and prefix (starts-with nx prefix)) (subseq nx (length prefix)) nx))
334          ;; Keep underscores, they are standards separators in Protobufs enum names
335          (name (remove-if-not #'(lambda (x) (or (alphanumericp x) (eql x #\_)))
336                               (format nil "~{~A~^_~}"
337                                       (split-string nx :separators *proto-name-separators*)))))
338     (values name (append ns (list name))
339             (format nil "~{~A~^.~}" (butlast xs)))))
340
341 ;; "slot-name" -> "slot_name", ("slot_name") or "slotName", ("slotName")
342 ;; "class-name.slot-name" -> "Class.slot_name", ("ClassName" "slot_name")
343 (defun slot-name->proto (x)
344   "Given a Lisp slot name, returns a Protobufs field name.
345    The second value is the fully qualified name, as a list."
346   (let* ((xs (split-string (string x) :separators '(#\.)))
347          (ns (loop for x in (butlast xs)
348                    collect (remove-if-not #'alphanumericp
349                                           (camel-case (format nil "~A" x) *proto-name-separators*))))
350          (nx (string-downcase (car (last xs))))
351          (name (if *camel-case-field-names*
352                  (remove-if-not #'alphanumericp
353                                 (camel-case-but-one (format nil "~A" nx) *proto-name-separators*))
354                  ;; Keep underscores, they are standards separators in Protobufs field names
355                  (remove-if-not #'(lambda (x) (or (alphanumericp x) (eql x #\_)))
356                                 (format nil "~{~A~^_~}"
357                                         (split-string nx :separators *proto-name-separators*))))))
358     (values name (append ns (list name))
359             (format nil "~{~A~^.~}" (butlast xs)))))
360
361
362 ;; "ClassName" -> 'class-name
363 ;; "cl-user.ClassName" -> 'cl-user::class-name
364 ;; "cl-user.OuterClass.InnerClass" -> 'cl-user::outer-class.inner-class
365 (defun proto->class-name (x &optional package)
366   "Given a Protobufs message or enum type name, returns a Lisp class or type name.
367    This resolves Protobufs qualified names as best as it can."
368   (let* ((xs (split-string (substitute #\- #\_ (uncamel-case x))
369                            :separators '(#\.)))
370          (pkg1 (and (cdr xs) (find-proto-package (first xs))))
371          (pkgn (and (cdr xs) (find-proto-package (butlast xs))))
372          (package (or pkg1 pkgn package))
373          (name (format nil "~{~A~^.~}" (if pkg1 (cdr xs) (if pkgn (last xs) xs)))))
374     (values (if package (intern name package) (make-symbol name)) package xs
375             ;; This might be the name of a package, too
376             (format nil "~{~A~^.~}" (butlast xs)))))
377
378 ;; "ENUM_VALUE" -> :enum-value
379 ;; "cl-user.ENUM_VALUE" -> :enum-value
380 ;; "cl-user.OuterClass.ENUM_VALUE" -> :enum-value
381 (defun proto->enum-name (x &optional package)
382   "Given a Protobufs enum value name, returns a Lisp enum value name.
383    This resolves Protobufs qualified names as best as it can."
384   (let* ((xs (split-string (substitute #\- #\_ (uncamel-case x))
385                            :separators '(#\.)))
386          (pkg1 (and (cdr xs) (find-proto-package (first xs))))
387          (pkgn (and (cdr xs) (find-proto-package (butlast xs))))
388          (package (or pkg1 pkgn package))
389          (name (format nil "~{~A~^.~}" (if pkg1 (cdr xs) (if pkgn (last xs) xs)))))
390     (values (kintern name) package xs
391             (format nil "~{~A~^.~}" (butlast xs)))))
392
393 ;; "slot_name" or "slotName" -> 'slot-name
394 ;; "cl-user.slot_name" or "cl-user.slotName" -> 'cl-user::slot-name
395 ;; "cl-user.OuterClass.slot_name" -> 'cl-user::outer-class.slot-name
396 (defun proto->slot-name (x &optional package)
397   "Given a Protobufs field value name, returns a Lisp slot name.
398    This resolves Protobufs qualified names as best as it can."
399   (let* ((xs (split-string (substitute #\- #\_ (uncamel-case x))
400                            :separators '(#\.)))
401          (pkg1 (and (cdr xs) (find-proto-package (first xs))))
402          (pkgn (and (cdr xs) (find-proto-package (butlast xs))))
403          (package (or pkg1 pkgn package))
404          (name (format nil "~{~A~^.~}" (if pkg1 (cdr xs) (if pkgn (last xs) xs)))))
405     (values (if package (intern name package) (make-symbol name)) package xs
406             (format nil "~{~A~^.~}" (butlast xs)))))
407
408
409 ;;; Warnings
410
411 (define-condition protobufs-warning (warning simple-condition) ())
412
413 (defun protobufs-warn (format-control &rest format-arguments)
414   (warn 'protobufs-warning
415         :format-control format-control
416         :format-arguments format-arguments))
417
418
419 #-(or allegro lispworks)
420 (defmacro without-redefinition-warnings (() &body body)
421   `(progn ,@body))
422     
423 #+allegro
424 (defmacro without-redefinition-warnings (() &body body)
425   `(excl:without-redefinition-warnings ,@body))
426
427 #+lispworks
428 (defmacro without-redefinition-warnings (() &body body)
429   `(let ((dspec:*redefinition-action* :quiet)) ,@body))
430
431 \f
432 ;;; Portable floating point utilities
433
434 #+(or abcl allegro cmu sbcl lispworks)
435 (defun single-float-bits (x)
436   (declare (type single-float x))
437   #+abcl    (system:single-float-bits x)
438   #+allegro (multiple-value-bind (high low)
439                 (excl:single-float-to-shorts x)
440               (declare (type (unsigned-byte 16) high low))
441               (logior (ash high 16) low))
442   #+cmu  (kernel:single-float-bits x)
443   #+sbcl (sb-kernel:single-float-bits x)
444   #+lispworks (lispworks-float:single-float-bits x))
445
446 #-(or abcl allegro cmu sbcl lispworks)
447 (defun single-float-bits (x)
448   (declare (type single-float x))
449   (assert (= (float-radix x) 2))
450   (if (zerop x)
451     (if (eql x 0.0f0) 0 #x-80000000)
452     (multiple-value-bind (lisp-significand lisp-exponent lisp-sign)
453         (integer-decode-float x)
454       (assert (plusp lisp-significand))
455       (let* ((significand lisp-significand)
456              (exponent (+ lisp-exponent 23 127))
457              (unsigned-result
458               (if (plusp exponent)                      ;if not obviously denormalized
459                 (do () (nil)
460                   (cond
461                     ;; Special termination case for denormalized float number
462                     ((zerop exponent)
463                      ;; Denormalized numbers have exponent one greater than
464                      ;; in the exponent field
465                      (return (ash significand -1)))
466                     ;; Ordinary termination case
467                     ((>= significand (expt 2 23))
468                      (assert (< 0 significand (expt 2 24)))
469                      ;; Exponent 0 is reserved for denormalized numbers,
470                      ;; and 255 is reserved for specials like NaN
471                      (assert (< 0 exponent 255))
472                      (return (logior (ash exponent 23)
473                                      (logand significand (1- (ash 1 23))))))
474                     (t
475                      ;; Shift as necessary to set bit 24 of significand
476                      (setq significand (ash significand 1)
477                            exponent (1- exponent)))))
478                 (do () ((zerop exponent)
479                         ;; Denormalized numbers have exponent one greater than
480                         ;; the exponent field
481                         (ash significand -1))
482                   (unless (zerop (logand significand 1))
483                     (warn "Denormalized '~S' losing bits in ~D" 'single-float-bits x))
484                   (setq significand (ash significand -1)
485                         exponent (1+ exponent))))))
486         (ecase lisp-sign
487           ((1)  unsigned-result)
488           ((-1) (logior unsigned-result (- (expt 2 31)))))))))
489
490
491 #+(or abcl allegro cmu sbcl lispworks)
492 (defun double-float-bits (x)
493   (declare (type double-float x))
494   #+abcl    (values (system:double-float-low-bits x)
495                     (system:double-float-high-bits x))
496   #+allegro (multiple-value-bind (us3 us2 us1 us0)
497                 (excl:double-float-to-shorts x)
498               (logior (ash us1 16) us0)
499               (logior (ash us3 16) us2))
500   #+cmu  (values (kernel:double-float-low-bits x)
501                  (kernel:double-float-high-bits x))
502   #+sbcl (values (sb-kernel:double-float-low-bits x)
503                  (sb-kernel:double-float-high-bits x))
504   #+lispworks (let ((bits (lispworks-float:double-float-bits x)))
505                 (values (logand #xffffffff bits)
506                         (ash bits -32))))
507
508 #-(or abcl allegro cmu sbcl lispworks)
509 (defun double-float-bits (x)
510   (declare (type double-float x))
511   (assert (= (float-radix x) 2))
512   (if (zerop x)
513     (if (eql x 0.0d0) 0 #x-8000000000000000)
514     (multiple-value-bind (lisp-significand lisp-exponent lisp-sign)
515         (integer-decode-float x)
516       (assert (plusp lisp-significand))
517       (let* ((significand lisp-significand)
518              (exponent (+ lisp-exponent 52 1023))
519              (unsigned-result
520               (if (plusp exponent)                      ;if not obviously denormalized
521                 (do () (nil)
522                   (cond
523                     ;; Special termination case for denormalized float number
524                     ((zerop exponent)
525                      ;; Denormalized numbers have exponent one greater than
526                      ;; in the exponent field
527                      (return (ash significand -1)))
528                     ;; Ordinary termination case
529                     ((>= significand (expt 2 52))
530                      (assert (< 0 significand (expt 2 53)))
531                      ;; Exponent 0 is reserved for denormalized numbers,
532                      ;; and 2047 is reserved for specials like NaN
533                      (assert (< 0 exponent 2047))
534                      (return (logior (ash exponent 52)
535                                      (logand significand (1- (ash 1 52))))))
536                     (t
537                      ;; Shift as necessary to set bit 53 of significand
538                      (setq significand (ash significand 1)
539                            exponent (1- exponent)))))
540                 (do () ((zerop exponent)
541                         ;; Denormalized numbers have exponent one greater than
542                         ;; the exponent field
543                         (ash significand -1))
544                   (unless (zerop (logand significand 1))
545                     (warn "Denormalized '~S' losing bits in ~D" 'double-float-bits x))
546                   (setq significand (ash significand -1)
547                         exponent (1+ exponent))))))
548         (let ((result
549                (ecase lisp-sign
550                  ((1)  unsigned-result)
551                  ((-1) (logior unsigned-result (- (expt 2 63)))))))
552           ;; Return the low bits and the high bits
553           (values (logand #xffffffff result) (ash result -32)))))))
554
555
556 #+(or abcl allegro cmu sbcl lispworks)
557 (defun make-single-float (bits)
558   (declare (type (signed-byte 32) bits))
559   #+abcl    (system:make-single-float bits)
560   #+allegro (excl:shorts-to-single-float (ldb (byte 16 16) bits)
561                                          (ldb (byte 16 0) bits))
562   #+cmu  (kernel:make-single-float bits)
563   #+sbcl (sb-kernel:make-single-float bits)
564   #+lispworks (lispworks-float:make-single-float bits))
565
566 #-(or abcl allegro cmu sbcl lispworks)
567 (defun make-single-float (bits)
568   (declare (type (signed-byte 32) bits))
569   (cond
570     ;; IEEE float special cases
571     ((zerop bits) 0.0)
572     ((= bits #x-80000000) -0.0)
573     (t
574      (let* ((sign (ecase (ldb (byte 1 31) bits)
575                     (0 1.0)
576                     (1 -1.0)))
577             (iexpt (ldb (byte 8 23) bits))
578             (exponent (if (zerop iexpt)                 ;denormalized
579                         -126
580                         (- iexpt 127)))
581             (mantissa (* (logior (ldb (byte 23 0) bits)
582                                  (if (zerop iexpt) 0 (ash 1 23)))
583                          (expt 0.5 23))))
584        (* sign (expt 2.0 exponent) mantissa)))))
585
586
587 #+(or abcl allegro cmu sbcl lispworks)
588 (defun make-double-float (low high)
589   (declare (type (unsigned-byte 32) low)
590            (type (signed-byte   32) high))
591   #+abcl (system:make-double-float (logior (ash high 32) low))
592   #+allegro (excl:shorts-to-double-float (ldb (byte 16 16) high)
593                                          (ldb (byte 16 0) high)
594                                          (ldb (byte 16 16) low)
595                                          (ldb (byte 16 0) low))
596   #+cmu  (kernel:make-double-float high low)
597   #+sbcl (sb-kernel:make-double-float high low)
598   #+lispworks (lispworks-float:make-double-float high low))
599
600 #-(or abcl allegro cmu sbcl lispworks)
601 (defun make-double-float (low high)
602   (declare (type (unsigned-byte 32) low)
603            (type (signed-byte   32) high))
604   (cond
605     ;; IEEE float special cases
606     ((and (zerop high) (zerop low)) 0.0d0)
607     ((and (= high #x-80000000)
608           (zerop low)) -0.0d0)
609     (t
610      (let* ((bits (logior (ash high 32) low))
611             (sign (ecase (ldb (byte 1 63) bits)
612                     (0 1.0d0)
613                     (1 -1.0d0)))
614             (iexpt (ldb (byte 11 52) bits))
615             (exponent (if (zerop iexpt)                 ;denormalized
616                         -1022
617                         (- iexpt 1023)))
618             (mantissa (* (logior (ldb (byte 52 0) bits)
619                                  (if (zerop iexpt) 0 (ash 1 52)))
620                          (expt 0.5d0 52))))
621        (* sign (expt 2.0d0 exponent) mantissa)))))