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