Restore building of +sb-unicode with -sb-unicode.
[sbcl.git] / src / code / target-char.lisp
1 ;;;; character functions
2
3 ;;;; This software is part of the SBCL system. See the README file for
4 ;;;; more information.
5 ;;;;
6 ;;;; This software is derived from the CMU CL system, which was
7 ;;;; written at Carnegie Mellon University and released into the
8 ;;;; public domain. The software is in the public domain and is
9 ;;;; provided with absolutely no warranty. See the COPYING and CREDITS
10 ;;;; files for more information.
11
12 (in-package "SB!IMPL")
13
14 ;;; We compile some trivial character operations via inline expansion.
15 #!-sb-fluid
16 (declaim (inline standard-char-p graphic-char-p alpha-char-p
17                  upper-case-p lower-case-p both-case-p alphanumericp
18                  char-int))
19 (declaim (maybe-inline digit-char-p digit-weight))
20
21 (deftype char-code ()
22   `(integer 0 (,sb!xc:char-code-limit)))
23
24 #!+sb-unicode
25 (progn
26  (defvar *unicode-character-name-database*)
27  (defvar *unicode-character-name-huffman-tree*))
28
29 (macrolet
30     ((frob ()
31        (flet ((file (name type)
32                 (merge-pathnames (make-pathname
33                                   :directory
34                                   '(:relative :up :up "output")
35                                   :name name :type type)
36                                  sb!xc:*compile-file-truename*))
37               (read-ub8-vector (pathname)
38                 (with-open-file (stream pathname
39                                         :direction :input
40                                         :element-type '(unsigned-byte 8))
41                   (let* ((length (file-length stream))
42                          (array (make-array
43                                  length :element-type '(unsigned-byte 8))))
44                     (read-sequence array stream)
45                     array))))
46          (let ((character-database (read-ub8-vector (file "ucd" "dat")))
47                (decompositions (read-ub8-vector (file "decomp" "dat")))
48                (long-decompositions (read-ub8-vector (file "ldecomp" "dat")))
49                (primary-compositions (read-ub8-vector (file "comp" "dat"))))
50            `(progn
51               (declaim (type (simple-array (unsigned-byte 8) (*))
52                              **character-database**
53                              **character-decompositions**
54                              **character-long-decompositions**))
55               (defglobal **character-database** ,character-database)
56               (defglobal **character-decompositions** ,decompositions)
57               (defglobal **character-long-decompositions** ,long-decompositions)
58               ;; KLUDGE: temporary value, fixed up in cold-load
59               (defglobal **character-primary-compositions** ,primary-compositions)
60               (defun !character-database-cold-init ()
61                 (setf **character-database** ,character-database)
62                 (setf **character-primary-compositions**
63                       (let ((table (make-hash-table))
64                             (info ,primary-compositions))
65                         (flet ((code (j)
66                                  (dpb (aref info (* 4 j))
67                                       (byte 8 24)
68                                       (dpb (aref info (+ (* 4 j) 1))
69                                            (byte 8 16)
70                                            (dpb (aref info (+ (* 4 j) 2))
71                                                 (byte 8 8)
72                                                 (aref info (+ (* 4 j) 3)))))))
73                           #!+sb-unicode
74                           (dotimes (i (/ (length info) 12))
75                             (setf (gethash (dpb (code (* 3 i)) (byte 21 21)
76                                                 (code (1+ (* 3 i))))
77                                            table)
78                                   (code-char (code (+ (* 3 i) 2)))))
79                           table))))
80               ,(with-open-file (stream (file "ucd-names" "lisp-expr")
81                                        :direction :input
82                                        :element-type 'character)
83                                (let ((names (make-hash-table)))
84                                  #!+sb-unicode
85                                  (loop
86                                        for code-point = (read stream nil nil)
87                                        for char-name = (string-upcase (read stream nil nil))
88                                        while code-point
89                                        do (setf (gethash code-point names) char-name))
90                                  (let ((tree
91                                         #!+sb-unicode
92                                          (make-huffman-tree
93                                           (let (list)
94                                             (maphash (lambda (code name)
95                                                        (declare (ignore code))
96                                                        (push name list))
97                                                      names)
98                                             list)))
99                                        (code->name
100                                         (make-array (hash-table-count names)
101                                                     :fill-pointer 0))
102                                        (name->code nil))
103                                    (maphash (lambda (code name)
104                                               (vector-push
105                                                (cons code (huffman-encode name tree))
106                                                code->name))
107                                             names)
108                                    (setf name->code
109                                          (sort (copy-seq code->name) #'< :key #'cdr))
110                                    (setf code->name
111                                          (sort (copy-seq name->code) #'< :key #'car))
112                                    (setf names nil)
113                                    `(defun !character-name-database-cold-init ()
114                                       #!+sb-unicode
115                                       (setq *unicode-character-name-database*
116                                             (cons ',code->name ',name->code)
117                                             *unicode-character-name-huffman-tree* ',tree))))))))))
118   (frob))
119 #+sb-xc-host (!character-name-database-cold-init)
120
121 (defparameter *base-char-name-alist*
122   ;; Note: The *** markers here indicate character names which are
123   ;; required by the ANSI specification of #'CHAR-NAME. For the others,
124   ;; we prefer the ASCII standard name.
125   '((#x00 "Nul" "Null" "^@")
126     (#x01 "Soh" "^a")
127     (#x02 "Stx" "^b")
128     (#x03 "Etx" "^c")
129     (#x04 "Eot" "^d")
130     (#x05 "Enq" "^e")
131     (#x06 "Ack" "^f")
132     (#x07 "Bel" "Bell" "^g")
133     (#x08 "Backspace" "^h" "Bs") ; *** See Note above
134     (#x09 "Tab" "^i" "Ht") ; *** See Note above
135     (#x0A "Newline" "Linefeed" "^j" "Lf" "Nl") ; *** See Note above
136     (#x0B "Vt" "^k")
137     (#x0C "Page" "^l" "Form" "Formfeed" "Ff" "Np") ; *** See Note above
138     (#x0D "Return" "^m" "Cr") ; *** See Note above
139     (#x0E "So" "^n")
140     (#x0F "Si" "^o")
141     (#x10 "Dle" "^p")
142     (#x11 "Dc1" "^q")
143     (#x12 "Dc2" "^r")
144     (#x13 "Dc3" "^s")
145     (#x14 "Dc4" "^t")
146     (#x15 "Nak" "^u")
147     (#x16 "Syn" "^v")
148     (#x17 "Etb" "^w")
149     (#x18 "Can" "^x")
150     (#x19 "Em" "^y")
151     (#x1A "Sub" "^z")
152     (#x1B "Esc" "Escape" "^[" "Altmode" "Alt")
153     (#x1C "Fs" "^\\")
154     (#x1D "Gs" "^]")
155     (#x1E "Rs" "^^")
156     (#x1F "Us" "^_")
157     (#x20 "Space" "Sp") ; *** See Note above
158     (#x7f "Rubout" "Delete" "Del")
159     (#x80 "C80")
160     (#x81 "C81")
161     (#x82 "Break-Permitted")
162     (#x83 "No-Break-Permitted")
163     (#x84 "C84")
164     (#x85 "Next-Line")
165     (#x86 "Start-Selected-Area")
166     (#x87 "End-Selected-Area")
167     (#x88 "Character-Tabulation-Set")
168     (#x89 "Character-Tabulation-With-Justification")
169     (#x8A "Line-Tabulation-Set")
170     (#x8B "Partial-Line-Forward")
171     (#x8C "Partial-Line-Backward")
172     (#x8D "Reverse-Linefeed")
173     (#x8E "Single-Shift-Two")
174     (#x8F "Single-Shift-Three")
175     (#x90 "Device-Control-String")
176     (#x91 "Private-Use-One")
177     (#x92 "Private-Use-Two")
178     (#x93 "Set-Transmit-State")
179     (#x94 "Cancel-Character")
180     (#x95 "Message-Waiting")
181     (#x96 "Start-Guarded-Area")
182     (#x97 "End-Guarded-Area")
183     (#x98 "Start-String")
184     (#x99 "C99")
185     (#x9A "Single-Character-Introducer")
186     (#x9B "Control-Sequence-Introducer")
187     (#x9C "String-Terminator")
188     (#x9D "Operating-System-Command")
189     (#x9E "Privacy-Message")
190     (#x9F "Application-Program-Command"))) ; *** See Note above
191 \f
192 ;;;; UCD accessor functions
193
194 ;;; The first (* 8 396) => 3168 entries in **CHARACTER-DATABASE**
195 ;;; contain entries for the distinct character attributes:
196 ;;; specifically, indexes into the GC kinds, Bidi kinds, CCC kinds,
197 ;;; the decimal digit property, the digit property and the
198 ;;; bidi-mirrored boolean property.  (There are two spare bytes for
199 ;;; other information, should that become necessary)
200 ;;;
201 ;;; the next (ash #x110000 -8) entries contain single-byte indexes
202 ;;; into a table of 256-element 4-byte-sized entries.  These entries
203 ;;; follow directly on, and are of the form
204 ;;; {attribute-index[11b],transformed-code-point[21b]}x256, where the
205 ;;; attribute index is an index into the miscellaneous information
206 ;;; table, and the transformed code point is the code point of the
207 ;;; simple mapping of the character to its lowercase or uppercase
208 ;;; equivalent, as appropriate and if any.
209 ;;;
210 ;;; I feel the opacity of the above suggests the need for a diagram:
211 ;;;
212 ;;;         C  _______________________________________
213 ;;;           /                                       \
214 ;;;          L                                         \
215 ;;;  [***************|=============================|--------...]
216 ;;;                 (a)      \                       _
217 ;;;                         A \______________________/| B
218 ;;;
219 ;;; To look up information about a character, take the high 13 bits of
220 ;;; its code point, and index the character database with that and a
221 ;;; base of 3168 (going past the miscellaneous information[*], so
222 ;;; treating (a) as the start of the array).  This, labelled A, gives
223 ;;; us another index into the detailed pages[-], which we can use to
224 ;;; look up the details for the character in question: we add the low
225 ;;; 8 bits of the character, shifted twice (because we have four-byte
226 ;;; table entries) to 1024 times the `page' index, with a base of 7520
227 ;;; to skip over everything else.  This gets us to point B.  If we're
228 ;;; after a transformed code point (i.e. an upcase or downcase
229 ;;; operation), we can simply read it off now, beginning with an
230 ;;; offset of 11 bits from point B in some endianness; if we're
231 ;;; looking for miscellaneous information, we take the 11-bit value at
232 ;;; B, and index the character database once more to get to the
233 ;;; relevant miscellaneous information.
234 ;;;
235 ;;; As an optimization to the common case (pun intended) of looking up
236 ;;; case information for a character, the entries in C above are
237 ;;; sorted such that the characters which are UPPER-CASE-P in CL terms
238 ;;; have index values lower than all others, followed by those which
239 ;;; are LOWER-CASE-P in CL terms; this permits implementation of
240 ;;; character case tests without actually going to the trouble of
241 ;;; looking up the value associated with the index.  (Actually, this
242 ;;; isn't just a speed optimization; the information about whether a
243 ;;; character is BOTH-CASE-P is used just in the ordering and not
244 ;;; explicitly recorded in the database).
245 ;;;
246 ;;; The moral of all this?  Next time, don't just say "FIXME: document
247 ;;; this"
248 (defun ucd-index (char)
249   (let* ((cp (char-code char))
250          (cp-high (ash cp -8))
251          (page (aref **character-database** (+ 3168 cp-high))))
252     (+ 7520 (ash page 10) (ash (ldb (byte 8 0) cp) 2))))
253
254 (declaim (ftype (sfunction (t) (unsigned-byte 11)) ucd-value-0))
255 (defun ucd-value-0 (char)
256   (let ((index (ucd-index char))
257         (character-database **character-database**))
258     (dpb (aref character-database index)
259          (byte 8 3)
260          (ldb (byte 3 5) (aref character-database (+ index 1))))))
261
262 (declaim (ftype (sfunction (t) (unsigned-byte 21)) ucd-value-1))
263 (defun ucd-value-1 (char)
264   (let ((index (ucd-index char))
265         (character-database **character-database**))
266     (dpb (aref character-database (+ index 1))
267          (byte 5 16)
268          (dpb (aref character-database (+ index 2))
269               (byte 8 8)
270               (aref character-database (+ index 3))))))
271
272 (declaim (ftype (sfunction (t) (unsigned-byte 8)) ucd-general-category))
273 (defun ucd-general-category (char)
274   (aref **character-database** (* 8 (ucd-value-0 char))))
275
276 (defun ucd-decimal-digit (char)
277   (let ((decimal-digit (aref **character-database**
278                              (+ 3 (* 8 (ucd-value-0 char))))))
279     (when (< decimal-digit 10)
280       decimal-digit)))
281 (declaim (ftype (sfunction (t) (unsigned-byte 8)) ucd-ccc))
282 (defun ucd-ccc (char)
283   (aref **character-database** (+ 2 (* 8 (ucd-value-0 char)))))
284
285 (defun char-code (char)
286   #!+sb-doc
287   "Return the integer code of CHAR."
288   (char-code char))
289
290 (defun char-int (char)
291   #!+sb-doc
292   "Return the integer code of CHAR. (In SBCL this is the same as CHAR-CODE, as
293 there are no character bits or fonts.)"
294   (char-code char))
295
296 (defun code-char (code)
297   #!+sb-doc
298   "Return the character with the code CODE."
299   (code-char code))
300
301 (defun character (object)
302   #!+sb-doc
303   "Coerce OBJECT into a CHARACTER if possible. Legal inputs are characters,
304 strings and symbols of length 1."
305   (flet ((do-error (control args)
306            (error 'simple-type-error
307                   :datum object
308                   ;;?? how to express "symbol with name of length 1"?
309                   :expected-type '(or character (string 1))
310                   :format-control control
311                   :format-arguments args)))
312     (typecase object
313       (character object)
314       (string (if (= 1 (length (the string object)))
315                   (char object 0)
316                   (do-error
317                    "String is not of length one: ~S" (list object))))
318       (symbol (if (= 1 (length (symbol-name object)))
319                   (schar (symbol-name object) 0)
320                   (do-error
321                    "Symbol name is not of length one: ~S" (list object))))
322       (t (do-error "~S cannot be coerced to a character." (list object))))))
323
324 (defun char-name (char)
325   #!+sb-doc
326   "Return the name (a STRING) for a CHARACTER object."
327   (let ((char-code (char-code char)))
328     (or (second (assoc char-code *base-char-name-alist*))
329         #!+sb-unicode
330         (let ((h-code (cdr (binary-search char-code
331                                           (car *unicode-character-name-database*)
332                                           :key #'car))))
333           (cond
334             (h-code
335              (huffman-decode h-code *unicode-character-name-huffman-tree*))
336             ((< char-code #x10000)
337              (format nil "U~4,'0X" char-code))
338             (t
339              (format nil "U~8,'0X" char-code)))))))
340
341 (defun name-char (name)
342   #!+sb-doc
343   "Given an argument acceptable to STRING, NAME-CHAR returns a character whose
344 name is that string, if one exists. Otherwise, NIL is returned."
345   (or (let ((char-code (car (rassoc-if (lambda (names)
346                                          (member name names :test #'string-equal))
347                                        *base-char-name-alist*))))
348         (when char-code
349           (code-char char-code)))
350       #!+sb-unicode
351       (let ((encoding (huffman-encode (string-upcase name)
352                                        *unicode-character-name-huffman-tree*)))
353         (when encoding
354           (let* ((char-code
355                   (car (binary-search encoding
356                                       (cdr *unicode-character-name-database*)
357                                       :key #'cdr)))
358                  (name-string (string name))
359                  (name-length (length name-string)))
360             (cond
361               (char-code
362                (code-char char-code))
363               ((and (or (= name-length 9)
364                         (= name-length 5))
365                     (char-equal (char name-string 0) #\U)
366                     (loop for i from 1 below name-length
367                           always (digit-char-p (char name-string i) 16)))
368                (code-char (parse-integer name-string :start 1 :radix 16)))
369               (t
370                nil)))))))
371 \f
372 ;;;; predicates
373
374 (defun standard-char-p (char)
375   #!+sb-doc
376   "The argument must be a character object. STANDARD-CHAR-P returns T if the
377 argument is a standard character -- one of the 95 ASCII printing characters or
378 <return>."
379   (and (typep char 'base-char)
380        (let ((n (char-code (the base-char char))))
381          (or (< 31 n 127)
382              (= n 10)))))
383
384 (defun %standard-char-p (thing)
385   #!+sb-doc
386   "Return T if and only if THING is a standard-char. Differs from
387 STANDARD-CHAR-P in that THING doesn't have to be a character."
388   (and (characterp thing) (standard-char-p thing)))
389
390 (defun graphic-char-p (char)
391   #!+sb-doc
392   "The argument must be a character object. GRAPHIC-CHAR-P returns T if the
393 argument is a printing character (space through ~ in ASCII), otherwise returns
394 NIL."
395   (let ((n (char-code char)))
396     (or (< 31 n 127)
397         (< 159 n))))
398
399 (defun alpha-char-p (char)
400   #!+sb-doc
401   "The argument must be a character object. ALPHA-CHAR-P returns T if the
402 argument is an alphabetic character, A-Z or a-z; otherwise NIL."
403   (< (ucd-general-category char) 5))
404
405 (defun upper-case-p (char)
406   #!+sb-doc
407   "The argument must be a character object; UPPER-CASE-P returns T if the
408 argument is an upper-case character, NIL otherwise."
409   (< (ucd-value-0 char) 5))
410
411 (defun lower-case-p (char)
412   #!+sb-doc
413   "The argument must be a character object; LOWER-CASE-P returns T if the
414 argument is a lower-case character, NIL otherwise."
415   (< 4 (ucd-value-0 char) 9))
416
417 (defun both-case-p (char)
418   #!+sb-doc
419   "The argument must be a character object. BOTH-CASE-P returns T if the
420 argument is an alphabetic character and if the character exists in both upper
421 and lower case. For ASCII, this is the same as ALPHA-CHAR-P."
422   (< (ucd-value-0 char) 9))
423
424 (defun digit-char-p (char &optional (radix 10.))
425   #!+sb-doc
426   "If char is a digit in the specified radix, returns the fixnum for which
427 that digit stands, else returns NIL."
428   (let ((m (- (char-code char) 48)))
429     (declare (fixnum m))
430     (cond ((<= radix 10.)
431            ;; Special-case decimal and smaller radices.
432            (if (and (>= m 0) (< m radix))  m  nil))
433           ;; Digits 0 - 9 are used as is, since radix is larger.
434           ((and (>= m 0) (< m 10)) m)
435           ;; Check for upper case A - Z.
436           ((and (>= (setq m (- m 7)) 10) (< m radix)) m)
437           ;; Also check lower case a - z.
438           ((and (>= (setq m (- m 32)) 10) (< m radix)) m)
439           ;; Else, fail.
440           (t (let ((number (ucd-decimal-digit char)))
441                (when (and number (< number radix))
442                  number))))))
443
444 (defun alphanumericp (char)
445   #!+sb-doc
446   "Given a character-object argument, ALPHANUMERICP returns T if the argument
447 is either numeric or alphabetic."
448   (let ((gc (ucd-general-category char)))
449     (or (< gc 5)
450         (= gc 12))))
451
452 (defun char= (character &rest more-characters)
453   #!+sb-doc
454   "Return T if all of the arguments are the same character."
455   (declare (truly-dynamic-extent more-characters))
456   (dolist (c more-characters t)
457     (declare (type character c))
458     (unless (eq c character) (return nil))))
459
460 (defun char/= (character &rest more-characters)
461   #!+sb-doc
462   "Return T if no two of the arguments are the same character."
463   (declare (truly-dynamic-extent more-characters))
464   (do* ((head character (car list))
465         (list more-characters (cdr list)))
466        ((null list) t)
467     (declare (type character head))
468     (dolist (c list)
469       (declare (type character c))
470       (when (eq head c) (return-from char/= nil)))))
471
472 (defun char< (character &rest more-characters)
473   #!+sb-doc
474   "Return T if the arguments are in strictly increasing alphabetic order."
475   (declare (truly-dynamic-extent more-characters))
476   (do* ((c character (car list))
477         (list more-characters (cdr list)))
478        ((null list) t)
479     (unless (< (char-int c)
480                (char-int (car list)))
481       (return nil))))
482
483 (defun char> (character &rest more-characters)
484   #!+sb-doc
485   "Return T if the arguments are in strictly decreasing alphabetic order."
486   (declare (truly-dynamic-extent more-characters))
487   (do* ((c character (car list))
488         (list more-characters (cdr list)))
489        ((null list) t)
490     (unless (> (char-int c)
491                (char-int (car list)))
492       (return nil))))
493
494 (defun char<= (character &rest more-characters)
495   #!+sb-doc
496   "Return T if the arguments are in strictly non-decreasing alphabetic order."
497   (declare (truly-dynamic-extent more-characters))
498   (do* ((c character (car list))
499         (list more-characters (cdr list)))
500        ((null list) t)
501     (unless (<= (char-int c)
502                 (char-int (car list)))
503       (return nil))))
504
505 (defun char>= (character &rest more-characters)
506   #!+sb-doc
507   "Return T if the arguments are in strictly non-increasing alphabetic order."
508   (declare (truly-dynamic-extent more-characters))
509   (do* ((c character (car list))
510         (list more-characters (cdr list)))
511        ((null list) t)
512     (unless (>= (char-int c)
513                 (char-int (car list)))
514       (return nil))))
515
516 ;;; EQUAL-CHAR-CODE is used by the following functions as a version of CHAR-INT
517 ;;;  which loses font, bits, and case info.
518
519 (defmacro equal-char-code (character)
520   (let ((ch (gensym)))
521     `(let ((,ch ,character))
522       (if (< (ucd-value-0 ,ch) 5)
523           (ucd-value-1 ,ch)
524           (char-code ,ch)))))
525
526 (defun two-arg-char-equal (c1 c2)
527   (flet ((base-char-equal-p ()
528            (let* ((code1 (char-code c1))
529                   (code2 (char-code c2))
530                   (sum (logxor code1 code2)))
531              (when (eql sum #x20)
532                (let ((sum (+ code1 code2)))
533                  (or (and (> sum 161) (< sum 213))
534                      (and (> sum 415) (< sum 461))
535                      (and (> sum 463) (< sum 477))))))))
536     (declare (inline base-char-equal-p))
537     (or (eq c1 c2)
538         #!-sb-unicode
539         (base-char-equal-p)
540         #!+sb-unicode
541         (typecase c1
542           (base-char
543            (and (base-char-p c2)
544                 (base-char-equal-p)))
545           (t
546            (= (equal-char-code c1) (equal-char-code c2)))))))
547
548 (defun char-equal-constant (x char reverse-case-char)
549   (declare (type character x))
550   (or (eq char x)
551       (eq reverse-case-char x)))
552
553 (defun char-equal (character &rest more-characters)
554   #!+sb-doc
555   "Return T if all of the arguments are the same character.
556 Case is ignored."
557   (declare (truly-dynamic-extent more-characters))
558   (do ((clist more-characters (cdr clist)))
559       ((null clist) t)
560     (unless (two-arg-char-equal (car clist) character)
561       (return nil))))
562
563 (defun two-arg-char-not-equal (c1 c2)
564   (/= (equal-char-code c1) (equal-char-code c2)))
565
566 (defun char-not-equal (character &rest more-characters)
567   #!+sb-doc
568   "Return T if no two of the arguments are the same character.
569 Case is ignored."
570   (declare (truly-dynamic-extent more-characters))
571   (do* ((head character (car list))
572         (list more-characters (cdr list)))
573        ((null list) t)
574     (unless (do* ((l list (cdr l)))
575                  ((null l) t)
576               (if (two-arg-char-equal head (car l))
577                   (return nil)))
578       (return nil))))
579
580 (defun two-arg-char-lessp (c1 c2)
581   (< (equal-char-code c1) (equal-char-code c2)))
582
583 (defun char-lessp (character &rest more-characters)
584   #!+sb-doc
585   "Return T if the arguments are in strictly increasing alphabetic order.
586 Case is ignored."
587   (declare (truly-dynamic-extent more-characters))
588   (do* ((c character (car list))
589         (list more-characters (cdr list)))
590        ((null list) t)
591     (unless (two-arg-char-lessp c (car list))
592       (return nil))))
593
594 (defun two-arg-char-greaterp (c1 c2)
595   (> (equal-char-code c1) (equal-char-code c2)))
596
597 (defun char-greaterp (character &rest more-characters)
598   #!+sb-doc
599   "Return T if the arguments are in strictly decreasing alphabetic order.
600 Case is ignored."
601   (declare (truly-dynamic-extent more-characters))
602   (do* ((c character (car list))
603         (list more-characters (cdr list)))
604        ((null list) t)
605     (unless (two-arg-char-greaterp c (car list))
606       (return nil))))
607
608 (defun two-arg-char-not-greaterp (c1 c2)
609   (<= (equal-char-code c1) (equal-char-code c2)))
610
611 (defun char-not-greaterp (character &rest more-characters)
612   #!+sb-doc
613   "Return T if the arguments are in strictly non-decreasing alphabetic order.
614 Case is ignored."
615   (declare (truly-dynamic-extent more-characters))
616   (do* ((c character (car list))
617         (list more-characters (cdr list)))
618        ((null list) t)
619     (unless (two-arg-char-not-greaterp c (car list))
620       (return nil))))
621
622 (defun two-arg-char-not-lessp (c1 c2)
623   (>= (equal-char-code c1) (equal-char-code c2)))
624
625 (defun char-not-lessp (character &rest more-characters)
626   #!+sb-doc
627   "Return T if the arguments are in strictly non-increasing alphabetic order.
628 Case is ignored."
629   (declare (truly-dynamic-extent more-characters))
630   (do* ((c character (car list))
631         (list more-characters (cdr list)))
632        ((null list) t)
633     (unless (two-arg-char-not-lessp c (car list))
634       (return nil))))
635 \f
636 ;;;; miscellaneous functions
637
638 (defun char-upcase (char)
639   #!+sb-doc
640   "Return CHAR converted to upper-case if that is possible. Don't convert
641 lowercase eszet (U+DF)."
642   (if (< 4 (ucd-value-0 char) 9)
643       (code-char (ucd-value-1 char))
644       char))
645
646 (defun char-downcase (char)
647   #!+sb-doc
648   "Return CHAR converted to lower-case if that is possible."
649   (if (< (ucd-value-0 char) 5)
650       (code-char (ucd-value-1 char))
651       char))
652
653 (defun digit-char (weight &optional (radix 10))
654   #!+sb-doc
655   "All arguments must be integers. Returns a character object that represents
656 a digit of the given weight in the specified radix. Returns NIL if no such
657 character exists."
658   (and (typep weight 'fixnum)
659        (>= weight 0) (< weight radix) (< weight 36)
660        (code-char (if (< weight 10) (+ 48 weight) (+ 55 weight)))))
661 \f
662 (defun char-decomposition-info (char)
663   (aref **character-database** (+ 6 (* 8 (ucd-value-0 char)))))
664
665 (defun char-decomposition (char)
666   (let* ((cp (char-code char))
667          (cp-high (ash cp -8))
668          (decompositions **character-decompositions**)
669          (long-decompositions **character-long-decompositions**)
670          (index (+ #x1100
671                    (ash (aref decompositions cp-high) 10)
672                    (ash (ldb (byte 8 0) cp) 2)))
673          (v0 (aref decompositions index))
674          (v1 (aref decompositions (+ index 1)))
675          (v2 (aref decompositions (+ index 2)))
676          (v3 (aref decompositions (+ index 3)))
677          (length (dpb v0 (byte 8 3) (ldb (byte 3 5) v1)))
678          (entry (dpb (ldb (byte 5 0) v1) (byte 5 16)
679                      (dpb v2 (byte 8 8) v3))))
680     (if (= length 1)
681         (string (code-char entry))
682         (if (<= #xac00 cp #xd7a3)
683             ;; see Unicode 6.2, section 3-12
684             (let* ((sbase #xac00)
685                    (lbase #x1100)
686                    (vbase #x1161)
687                    (tbase #x11a7)
688                    (lcount 19)
689                    (vcount 21)
690                    (tcount 28)
691                    (ncount (* vcount tcount))
692                    (scount (* lcount ncount))
693                    (sindex (- cp sbase))
694                    (lindex (floor sindex ncount))
695                    (vindex (floor (mod sindex ncount) tcount))
696                    (tindex (mod sindex tcount))
697                    (result (make-string length)))
698               (declare (ignore scount))
699               (setf (char result 0) (code-char (+ lbase lindex)))
700               (setf (char result 1) (code-char (+ vbase vindex)))
701               (when (> tindex 0)
702                 (setf (char result 2) (code-char (+ tbase tindex))))
703               result)
704             (let ((result (make-string length))
705                   (e (* 4 entry)))
706               (dotimes (i length result)
707                 (let ((code (dpb (aref long-decompositions (+ e 1))
708                                  (byte 8 16)
709                                  (dpb (aref long-decompositions (+ e 2))
710                                       (byte 8 8)
711                                       (aref long-decompositions (+ e 3))))))
712                   (setf (char result i) (code-char code)))
713                 (incf e 4)))))))
714
715 (defun decompose-char (char)
716   (if (= (char-decomposition-info char) 0)
717       (string char)
718       (char-decomposition char)))
719
720 (defun decompose-string (string &optional (kind :canonical))
721   (declare (type (member :canonical :compatibility) kind))
722   (flet ((canonical (char)
723            (= 1 (char-decomposition-info char)))
724          (compat (char)
725            (/= 0 (char-decomposition-info char))))
726     (let (result
727           (fun (ecase kind
728                  (:canonical #'canonical)
729                  (:compatibility #'compat))))
730       (do* ((start 0 (1+ end))
731             (end (position-if fun string :start start)
732                  (position-if fun string :start start)))
733            ((null end) (push (subseq string start end) result))
734         (unless (= start end)
735           (push (subseq string start end) result))
736         ;; FIXME: this recursive call to DECOMPOSE-STRING is necessary
737         ;; for correctness given our direct encoding of the
738         ;; decomposition data in UnicodeData.txt.  It would, however,
739         ;; be straightforward enough to perform the recursion in table
740         ;; construction, and then have this simply revert to a single
741         ;; lookup.  (Wait for tests to be hooked in, then implement).
742         (push (decompose-string (decompose-char (char string end)) kind)
743               result))
744       (apply 'concatenate 'string (nreverse result)))))
745
746 (defun sort-combiners (string)
747   (let (result (start 0) first-cc first-non-cc)
748     (tagbody
749      again
750        (setf first-cc (position 0 string :key #'ucd-ccc :test #'/= :start start))
751        (when first-cc
752          (setf first-non-cc (position 0 string :key #'ucd-ccc :test #'= :start first-cc)))
753        (push (subseq string start first-cc) result)
754        (when first-cc
755          (push (stable-sort (subseq string first-cc first-non-cc) #'< :key #'ucd-ccc) result))
756        (when first-non-cc
757          (setf start first-non-cc first-cc nil first-non-cc nil)
758          (go again)))
759     (apply 'concatenate 'string (nreverse result))))
760
761 (defun primary-composition (char1 char2)
762   (let ((c1 (char-code char1))
763         (c2 (char-code char2)))
764     (cond
765       ((gethash (dpb (char-code char1) (byte 21 21) (char-code char2))
766                 **character-primary-compositions**))
767       ((and (<= #x1100 c1) (<= c1 #x1112)
768             (<= #x1161 c2) (<= c2 #x1175))
769        (let ((lindex (- c1 #x1100))
770              (vindex (- c2 #x1161)))
771          (code-char (+ #xac00 (* lindex 588) (* vindex 28)))))
772       ((and (<= #xac00 c1) (<= c1 #.(+ #xac00 11171))
773             (<= #x11a8 c2) (<= c2 #x11c2)
774             (= 0 (rem (- c1 #xac00) 28)))
775        (code-char (+ c1 (- c2 #x11a7)))))))
776
777 ;;; This implements a sequence data structure, specialized for
778 ;;; efficient deletion of characters at an index, along with tolerable
779 ;;; random access.  The purpose is to support the canonical
780 ;;; composition algorithm from Unicode, which involves replacing (not
781 ;;; necessarily consecutive) pairs of code points with a single code
782 ;;; point (e.g. [#\e #\combining_acute_accent] with
783 ;;; #\latin_small_letter_e_with_acute).  The data structure is a list
784 ;;; of three-element lists, each denoting a chunk of string data
785 ;;; starting at the first index and ending at the second.
786 ;;;
787 ;;; Actually, the implementation isn't particularly efficient, and
788 ;;; would probably benefit from being rewritten in terms of displaced
789 ;;; arrays, which would substantially reduce copying.
790 ;;;
791 ;;; (also, generic sequences.  *sigh*.)
792 (defun lref (lstring index)
793   (dolist (l lstring)
794     (when (and (<= (first l) index)
795                (< index (second l)))
796       (return (aref (third l) (- index (first l)))))))
797 (defun (setf lref) (newchar lstring index)
798   (dolist (l lstring)
799     (when (and (<= (first l) index)
800                (< index (second l)))
801       (return (setf (aref (third l) (- index (first l))) newchar)))))
802 (defun llength (lstring)
803   (second (first (last lstring))))
804 (defun lstring (lstring)
805   (let ((result (make-string (llength lstring))))
806     (dolist (l lstring result)
807       (replace result (third l) :start1 (first l) :end1 (second l)))))
808 (defun ldelete (lstring index)
809   (do* ((ls lstring (cdr ls))
810         (l (car ls) (car ls))
811         so-fars)
812        ((and (<= (first l) index)
813              (< index (second l)))
814         (append
815          (nreverse so-fars)
816          (cond
817            ((= (first l) index)
818             (list (list (first l) (1- (second l)) (subseq (third l) 1))))
819            ((= index (1- (second l)))
820             (list (list (first l) (1- (second l)) (subseq (third l) 0 (1- (length (third l)))))))
821            (t
822             (list
823              (list (first l) index
824                    (subseq (third l) 0 (- index (first l))))
825              (list index (1- (second l))
826                    (subseq (third l) (1+ (- index (first l))))))))
827          (mapcar (lambda (x) (list (1- (first x)) (1- (second x)) (third x)))
828                  (cdr ls))))
829     (push l so-fars)))
830
831 (defun canonically-compose (string)
832   (labels ()
833     (let* ((result (list (list 0 (length string) string)))
834            (previous-starter-index (position 0 string :key #'ucd-ccc))
835            (i (and previous-starter-index (1+ previous-starter-index))))
836       (when (or (not i) (= i (length string)))
837         (return-from canonically-compose string))
838       (tagbody
839        again
840          (when (and (>= (- i previous-starter-index) 2)
841                     ;; test for Blocked (Unicode 3.11 para. D115)
842                     ;;
843                     ;; (assumes here that string has sorted combiners,
844                     ;; so can look back just one step)
845                     (>= (ucd-ccc (lref result (1- i)))
846                         (ucd-ccc (lref result i))))
847            (when (= (ucd-ccc (lref result i)) 0)
848              (setf previous-starter-index i))
849            (incf i)
850            (go next))
851
852          (let ((comp (primary-composition (lref result previous-starter-index)
853                                           (lref result i))))
854            (cond
855              (comp
856               (setf (lref result previous-starter-index) comp)
857               (setf result (ldelete result i)))
858              (t
859               (when (= (ucd-ccc (lref result i)) 0)
860                 (setf previous-starter-index i))
861               (incf i))))
862        next
863          (unless (= i (llength result))
864            (go again)))
865       (if (= i (length string))
866           string
867           (lstring result)))))
868
869 (defun normalize-string (string &optional (form :nfd))
870   (declare (type (member :nfd :nfkd :nfc :nfkc) form))
871   #!-sb-unicode
872   (etypecase string
873     ((array nil (*)) string)
874     (string
875      (ecase form
876        ((:nfc :nfkc) string)
877        ((:nfd :nfkd) (error "Cannot normalize to ~A form in #-SB-UNICODE builds" form)))))
878   #!+sb-unicode
879   (etypecase string
880     (base-string string)
881     ((array character (*))
882      (ecase form
883        ((:nfc)
884         (canonically-compose (sort-combiners (decompose-string string))))
885        ((:nfd)
886         (sort-combiners (decompose-string string)))
887        ((:nfkc)
888         (canonically-compose (sort-combiners (decompose-string string :compatibility))))
889        ((:nfkd)
890         (sort-combiners (decompose-string string :compatibility)))))
891     ((array nil (*)) string)))