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