f055e416ecb418bcb89cbec44e9e9ba4d47229de
[sbcl.git] / src / code / target-char.lisp
1 ;;;; character functions
2 ;;;;
3 ;;;; This implementation assumes the use of ASCII codes and the
4 ;;;; specific character formats used in SBCL (and its ancestor, CMU
5 ;;;; CL). It is optimized for performance rather than for portability
6 ;;;; and elegance, and may have to be rewritten if the character
7 ;;;; representation is changed.
8 ;;;;
9 ;;;; KLUDGE: As of sbcl-0.6.11.25, at least, the ASCII-dependence is
10 ;;;; not confined to this file. E.g. there are DEFTRANSFORMs in
11 ;;;; srctran.lisp for CHAR-UPCASE, CHAR-EQUAL, and CHAR-DOWNCASE, and
12 ;;;; they assume ASCII. -- WHN 2001-03-25
13
14 ;;;; This software is part of the SBCL system. See the README file for
15 ;;;; more information.
16 ;;;;
17 ;;;; This software is derived from the CMU CL system, which was
18 ;;;; written at Carnegie Mellon University and released into the
19 ;;;; public domain. The software is in the public domain and is
20 ;;;; provided with absolutely no warranty. See the COPYING and CREDITS
21 ;;;; files for more information.
22
23 (in-package "SB!IMPL")
24
25 ;;; We compile some trivial character operations via inline expansion.
26 #!-sb-fluid
27 (declaim (inline standard-char-p graphic-char-p alpha-char-p
28                  upper-case-p lower-case-p both-case-p alphanumericp
29                  char-int))
30 (declaim (maybe-inline digit-char-p digit-weight))
31
32 (deftype char-code ()
33   `(integer 0 (,char-code-limit)))
34
35 (defvar *character-database*)
36 (declaim (type (simple-array (unsigned-byte 8) (*)) *character-database*))
37
38 #!+sb-unicode
39 (progn
40  (defvar *unicode-character-name-database*)
41  (defvar *unicode-character-name-huffman-tree*))
42
43 (macrolet ((frob ()
44              (flet ((file (name type)
45                       (merge-pathnames (make-pathname
46                                         :directory
47                                         '(:relative :up :up "output")
48                                         :name name :type type)
49                                        sb!xc:*compile-file-truename*)))
50                `(progn
51                   ,(with-open-file (stream (file "ucd" "dat")
52                                            :direction :input
53                                            :element-type '(unsigned-byte 8))
54                      (let* ((length (file-length stream))
55                             (array (make-array
56                                     length :element-type '(unsigned-byte 8))))
57                        (read-sequence array stream)
58                        `(defun !character-database-cold-init ()
59                           (setq *character-database* ',array))))
60                   ,(with-open-file (stream (file "ucd-names" "lisp-expr")
61                                            :direction :input
62                                            :element-type 'character)
63                      (let ((names (make-hash-table)))
64                        #!+sb-unicode
65                        (loop
66                           for code-point = (read stream nil nil)
67                           for char-name = (string-upcase (read stream nil nil))
68                           while code-point
69                           do (setf (gethash code-point names) char-name))
70                        (let ((tree
71                               #!+sb-unicode
72                                (make-huffman-tree
73                                 (let (list)
74                                       (maphash (lambda (code name)
75                                                  (declare (ignore code))
76                                                  (push name list))
77                                                names)
78                                       list)))
79                              (code->name
80                               (make-array (hash-table-count names)
81                                           :fill-pointer 0))
82                              (name->code nil))
83                          (maphash (lambda (code name)
84                                     (vector-push
85                                      (cons code (huffman-encode name tree))
86                                      code->name))
87                                    names)
88                          (setf name->code
89                                (sort (copy-seq code->name) #'< :key #'cdr))
90                          (setf code->name
91                                (sort (copy-seq name->code) #'< :key #'car))
92                          (setf names nil)
93                          `(defun !character-name-database-cold-init ()
94                             #!+sb-unicode
95                             (setq *unicode-character-name-database*
96                                   (cons ',code->name ',name->code)
97                                   *unicode-character-name-huffman-tree* ',tree)))))))))
98   (frob))
99 #+sb-xc-host (!character-database-cold-init)
100 #+sb-xc-host (!character-name-database-cold-init)
101
102 (defparameter *base-char-name-alist*
103   ;; Note: The *** markers here indicate character names which are
104   ;; required by the ANSI specification of #'CHAR-NAME. For the others,
105   ;; we prefer the ASCII standard name.
106   '((#x00 "Nul" "Null" "^@")
107     (#x01 "Soh" "^a")
108     (#x02 "Stx" "^b")
109     (#x03 "Etx" "^c")
110     (#x04 "Eot" "^d")
111     (#x05 "Enq" "^e")
112     (#x06 "Ack" "^f")
113     (#x07 "Bel" "Bell" "^g")
114     (#x08 "Backspace" "^h" "Bs") ; *** See Note above
115     (#x09 "Tab" "^i" "Ht") ; *** See Note above
116     (#x0A "Newline" "Linefeed" "^j" "Lf" "Nl") ; *** See Note above
117     (#x0B "Vt" "^k")
118     (#x0C "Page" "^l" "Form" "Formfeed" "Ff" "Np") ; *** See Note above
119     (#x0D "Return" "^m" "Cr") ; *** See Note above
120     (#x0E "So" "^n")
121     (#x0F "Si" "^o")
122     (#x10 "Dle" "^p")
123     (#x11 "Dc1" "^q")
124     (#x12 "Dc2" "^r")
125     (#x13 "Dc3" "^s")
126     (#x14 "Dc4" "^t")
127     (#x15 "Nak" "^u")
128     (#x16 "Syn" "^v")
129     (#x17 "Etb" "^w")
130     (#x18 "Can" "^x")
131     (#x19 "Em" "^y")
132     (#x1A "Sub" "^z")
133     (#x1B "Esc" "Escape" "^[" "Altmode" "Alt")
134     (#x1C "Fs" "^\\")
135     (#x1D "Gs" "^]")
136     (#x1E "Rs" "^^")
137     (#x1F "Us" "^_")
138     (#x20 "Space" "Sp") ; *** See Note above
139     (#x7f "Rubout" "Delete" "Del")
140     (#x80 "C80")
141     (#x81 "C81")
142     (#x82 "Break-Permitted")
143     (#x83 "No-Break-Permitted")
144     (#x84 "C84")
145     (#x85 "Next-Line")
146     (#x86 "Start-Selected-Area")
147     (#x87 "End-Selected-Area")
148     (#x88 "Character-Tabulation-Set")
149     (#x89 "Character-Tabulation-With-Justification")
150     (#x8A "Line-Tabulation-Set")
151     (#x8B "Partial-Line-Forward")
152     (#x8C "Partial-Line-Backward")
153     (#x8D "Reverse-Linefeed")
154     (#x8E "Single-Shift-Two")
155     (#x8F "Single-Shift-Three")
156     (#x90 "Device-Control-String")
157     (#x91 "Private-Use-One")
158     (#x92 "Private-Use-Two")
159     (#x93 "Set-Transmit-State")
160     (#x94 "Cancel-Character")
161     (#x95 "Message-Waiting")
162     (#x96 "Start-Guarded-Area")
163     (#x97 "End-Guarded-Area")
164     (#x98 "Start-String")
165     (#x99 "C99")
166     (#x9A "Single-Character-Introducer")
167     (#x9B "Control-Sequence-Introducer")
168     (#x9C "String-Terminator")
169     (#x9D "Operating-System-Command")
170     (#x9E "Privacy-Message")
171     (#x9F "Application-Program-Command"))) ; *** See Note above
172 \f
173 ;;;; accessor functions
174
175 ;; (* 8 186) => 1488
176 ;; (+ 1488 (ash #x110000 -8)) => 5840
177 (defun ucd-index (char)
178   (let* ((cp (char-code char))
179          (cp-high (ash cp -8))
180          (page (aref *character-database* (+ 1488 cp-high))))
181     (+ 5840 (ash page 10) (ash (ldb (byte 8 0) cp) 2))))
182
183 (defun ucd-value-0 (char)
184   (aref *character-database* (ucd-index char)))
185
186 (defun ucd-value-1 (char)
187   (let ((index (ucd-index char)))
188     (dpb (aref *character-database* (+ index 3))
189          (byte 8 16)
190          (dpb (aref *character-database* (+ index 2))
191               (byte 8 8)
192               (aref *character-database* (1+ index))))))
193
194 (defun ucd-general-category (char)
195   (aref *character-database* (* 8 (ucd-value-0 char))))
196
197 (defun ucd-decimal-digit (char)
198   (let ((decimal-digit (aref *character-database*
199                              (+ 3 (* 8 (ucd-value-0 char))))))
200     (when (< decimal-digit 10)
201       decimal-digit)))
202
203 (defun char-code (char)
204   #!+sb-doc
205   "Return the integer code of CHAR."
206   ;; FIXME: do we actually need this?
207   (etypecase char
208     (character (char-code (truly-the character char)))))
209
210 (defun char-int (char)
211   #!+sb-doc
212   "Return the integer code of CHAR. (In SBCL this is the same as CHAR-CODE, as
213    there are no character bits or fonts.)"
214   (char-code char))
215
216 (defun code-char (code)
217   #!+sb-doc
218   "Return the character with the code CODE."
219   (code-char code))
220
221 (defun character (object)
222   #!+sb-doc
223   "Coerce OBJECT into a CHARACTER if possible. Legal inputs are
224   characters, strings and symbols of length 1."
225   (flet ((do-error (control args)
226            (error 'simple-type-error
227                   :datum object
228                   ;;?? how to express "symbol with name of length 1"?
229                   :expected-type '(or character (string 1))
230                   :format-control control
231                   :format-arguments args)))
232     (typecase object
233       (character object)
234       (string (if (= 1 (length (the string object)))
235                   (char object 0)
236                   (do-error
237                    "String is not of length one: ~S" (list object))))
238       (symbol (if (= 1 (length (symbol-name object)))
239                   (schar (symbol-name object) 0)
240                   (do-error
241                    "Symbol name is not of length one: ~S" (list object))))
242       (t (do-error "~S cannot be coerced to a character." (list object))))))
243
244 (defun char-name (char)
245   #!+sb-doc
246   "Return the name (a STRING) for a CHARACTER object."
247   (let ((char-code (char-code char)))
248     (or (second (assoc char-code *base-char-name-alist*))
249         #!+sb-unicode
250         (let ((h-code (cdr (binary-search char-code
251                                           (car *unicode-character-name-database*)
252                                           :key #'car))))
253           (cond
254             (h-code
255              (huffman-decode h-code *unicode-character-name-huffman-tree*))
256             ((< char-code #x10000)
257              (format nil "U~4,'0X" char-code))
258             (t
259              (format nil "U~8,'0X" char-code)))))))
260
261 (defun name-char (name)
262   #!+sb-doc
263   "Given an argument acceptable to STRING, NAME-CHAR returns a character
264   whose name is that string, if one exists. Otherwise, NIL is returned."
265   (or (let ((char-code (car (rassoc-if (lambda (names)
266                                          (member name names :test #'string-equal))
267                                        *base-char-name-alist*))))
268         (when char-code
269           (code-char char-code)))
270       #!+sb-unicode
271       (let ((encoding (huffman-encode (string-upcase name)
272                                        *unicode-character-name-huffman-tree*)))
273         (when encoding
274           (let* ((char-code
275                   (car (binary-search encoding
276                                       (cdr *unicode-character-name-database*)
277                                       :key #'cdr)))
278                  (name-string (string name))
279                  (name-length (length name-string)))
280             (cond
281               (char-code
282                (code-char char-code))
283               ((and (or (= name-length 9)
284                         (= name-length 5))
285                     (char-equal (char name-string 0) #\U)
286                     (loop for i from 1 below name-length
287                           always (digit-char-p (char name-string i) 16)))
288                (code-char (parse-integer name-string :start 1 :radix 16)))
289               (t
290                nil)))))))
291 \f
292 ;;;; predicates
293
294 (defun standard-char-p (char)
295   #!+sb-doc
296   "The argument must be a character object. STANDARD-CHAR-P returns T if the
297    argument is a standard character -- one of the 95 ASCII printing characters
298    or <return>."
299   (and (typep char 'base-char)
300        (let ((n (char-code (the base-char char))))
301          (or (< 31 n 127)
302              (= n 10)))))
303
304 (defun %standard-char-p (thing)
305   #!+sb-doc
306   "Return T if and only if THING is a standard-char. Differs from
307   STANDARD-CHAR-P in that THING doesn't have to be a character."
308   (and (characterp thing) (standard-char-p thing)))
309
310 (defun graphic-char-p (char)
311   #!+sb-doc
312   "The argument must be a character object. GRAPHIC-CHAR-P returns T if the
313   argument is a printing character (space through ~ in ASCII), otherwise
314   returns NIL."
315   (let ((n (char-code char)))
316     (or (< 31 n 127)
317         (< 159 n))))
318
319 (defun alpha-char-p (char)
320   #!+sb-doc
321   "The argument must be a character object. ALPHA-CHAR-P returns T if the
322    argument is an alphabetic character, A-Z or a-z; otherwise NIL."
323   (< (ucd-general-category char) 5))
324
325 (defun upper-case-p (char)
326   #!+sb-doc
327   "The argument must be a character object; UPPER-CASE-P returns T if the
328    argument is an upper-case character, NIL otherwise."
329   (= (ucd-value-0 char) 0))
330
331 (defun lower-case-p (char)
332   #!+sb-doc
333   "The argument must be a character object; LOWER-CASE-P returns T if the
334    argument is a lower-case character, NIL otherwise."
335   (= (ucd-value-0 char) 1))
336
337 (defun both-case-p (char)
338   #!+sb-doc
339   "The argument must be a character object. BOTH-CASE-P returns T if the
340   argument is an alphabetic character and if the character exists in
341   both upper and lower case. For ASCII, this is the same as ALPHA-CHAR-P."
342   (< (ucd-value-0 char) 2))
343
344 (defun digit-char-p (char &optional (radix 10.))
345   #!+sb-doc
346   "If char is a digit in the specified radix, returns the fixnum for
347   which that digit stands, else returns NIL."
348   (let ((m (- (char-code char) 48)))
349     (declare (fixnum m))
350     (cond ((<= radix 10.)
351            ;; Special-case decimal and smaller radices.
352            (if (and (>= m 0) (< m radix))  m  nil))
353           ;; Digits 0 - 9 are used as is, since radix is larger.
354           ((and (>= m 0) (< m 10)) m)
355           ;; Check for upper case A - Z.
356           ((and (>= (setq m (- m 7)) 10) (< m radix)) m)
357           ;; Also check lower case a - z.
358           ((and (>= (setq m (- m 32)) 10) (< m radix)) m)
359           ;; Else, fail.
360           (t (let ((number (ucd-decimal-digit char)))
361                (when (and number (< number radix))
362                  number))))))
363
364 (defun alphanumericp (char)
365   #!+sb-doc
366   "Given a character-object argument, ALPHANUMERICP returns T if the
367    argument is either numeric or alphabetic."
368   (let ((gc (ucd-general-category char)))
369     (or (< gc 5)
370         (= gc 12))))
371
372 (defun char= (character &rest more-characters)
373   #!+sb-doc
374   "Return T if all of the arguments are the same character."
375   (declare (dynamic-extent more-characters))
376   (dolist (c more-characters t)
377     (declare (type character c))
378     (unless (eq c character) (return nil))))
379
380 (defun char/= (character &rest more-characters)
381   #!+sb-doc
382   "Return T if no two of the arguments are the same character."
383   (declare (dynamic-extent more-characters))
384   (do* ((head character (car list))
385         (list more-characters (cdr list)))
386        ((null list) t)
387     (declare (type character head))
388     (dolist (c list)
389       (declare (type character c))
390       (when (eq head c) (return-from char/= nil)))))
391
392 (defun char< (character &rest more-characters)
393   #!+sb-doc
394   "Return T if the arguments are in strictly increasing alphabetic order."
395   (declare (dynamic-extent more-characters))
396   (do* ((c character (car list))
397         (list more-characters (cdr list)))
398        ((null list) t)
399     (unless (< (char-int c)
400                (char-int (car list)))
401       (return nil))))
402
403 (defun char> (character &rest more-characters)
404   #!+sb-doc
405   "Return T if the arguments are in strictly decreasing alphabetic order."
406   (declare (dynamic-extent more-characters))
407   (do* ((c character (car list))
408         (list more-characters (cdr list)))
409        ((null list) t)
410     (unless (> (char-int c)
411                (char-int (car list)))
412       (return nil))))
413
414 (defun char<= (character &rest more-characters)
415   #!+sb-doc
416   "Return T if the arguments are in strictly non-decreasing alphabetic order."
417   (declare (dynamic-extent more-characters))
418   (do* ((c character (car list))
419         (list more-characters (cdr list)))
420        ((null list) t)
421     (unless (<= (char-int c)
422                 (char-int (car list)))
423       (return nil))))
424
425 (defun char>= (character &rest more-characters)
426   #!+sb-doc
427   "Return T if the arguments are in strictly non-increasing alphabetic order."
428   (declare (dynamic-extent more-characters))
429   (do* ((c character (car list))
430         (list more-characters (cdr list)))
431        ((null list) t)
432     (unless (>= (char-int c)
433                 (char-int (car list)))
434       (return nil))))
435
436 ;;; EQUAL-CHAR-CODE is used by the following functions as a version of CHAR-INT
437 ;;;  which loses font, bits, and case info.
438
439 (defmacro equal-char-code (character)
440   (let ((ch (gensym)))
441     `(let ((,ch ,character))
442       (if (= (ucd-value-0 ,ch) 0)
443           (ucd-value-1 ,ch)
444           (char-code ,ch)))))
445
446 (defun two-arg-char-equal (c1 c2)
447   (= (equal-char-code c1) (equal-char-code c2)))
448
449 (defun char-equal (character &rest more-characters)
450   #!+sb-doc
451   "Return T if all of the arguments are the same character.
452   Font, bits, and case are ignored."
453   (declare (dynamic-extent more-characters))
454   (do ((clist more-characters (cdr clist)))
455       ((null clist) t)
456     (unless (two-arg-char-equal (car clist) character)
457       (return nil))))
458
459 (defun two-arg-char-not-equal (c1 c2)
460   (/= (equal-char-code c1) (equal-char-code c2)))
461
462 (defun char-not-equal (character &rest more-characters)
463   #!+sb-doc
464   "Return T if no two of the arguments are the same character.
465    Font, bits, and case are ignored."
466   (declare (dynamic-extent more-characters))
467   (do* ((head character (car list))
468         (list more-characters (cdr list)))
469        ((null list) t)
470     (unless (do* ((l list (cdr l)))
471                  ((null l) t)
472               (if (two-arg-char-equal head (car l))
473                   (return nil)))
474       (return nil))))
475
476 (defun two-arg-char-lessp (c1 c2)
477   (< (equal-char-code c1) (equal-char-code c2)))
478
479 (defun char-lessp (character &rest more-characters)
480   #!+sb-doc
481   "Return T if the arguments are in strictly increasing alphabetic order.
482    Font, bits, and case are ignored."
483   (declare (dynamic-extent more-characters))
484   (do* ((c character (car list))
485         (list more-characters (cdr list)))
486        ((null list) t)
487     (unless (two-arg-char-lessp c (car list))
488       (return nil))))
489
490 (defun two-arg-char-greaterp (c1 c2)
491   (> (equal-char-code c1) (equal-char-code c2)))
492
493 (defun char-greaterp (character &rest more-characters)
494   #!+sb-doc
495   "Return T if the arguments are in strictly decreasing alphabetic order.
496    Font, bits, and case are ignored."
497   (declare (dynamic-extent more-characters))
498   (do* ((c character (car list))
499         (list more-characters (cdr list)))
500        ((null list) t)
501     (unless (two-arg-char-greaterp c (car list))
502       (return nil))))
503
504 (defun two-arg-char-not-greaterp (c1 c2)
505   (<= (equal-char-code c1) (equal-char-code c2)))
506
507 (defun char-not-greaterp (character &rest more-characters)
508   #!+sb-doc
509   "Return T if the arguments are in strictly non-decreasing alphabetic order.
510    Font, bits, and case are ignored."
511   (declare (dynamic-extent more-characters))
512   (do* ((c character (car list))
513         (list more-characters (cdr list)))
514        ((null list) t)
515     (unless (two-arg-char-not-greaterp c (car list))
516       (return nil))))
517
518 (defun two-arg-char-not-lessp (c1 c2)
519   (>= (equal-char-code c1) (equal-char-code c2)))
520
521 (defun char-not-lessp (character &rest more-characters)
522   #!+sb-doc
523   "Return T if the arguments are in strictly non-increasing alphabetic order.
524    Font, bits, and case are ignored."
525   (declare (dynamic-extent more-characters))
526   (do* ((c character (car list))
527         (list more-characters (cdr list)))
528        ((null list) t)
529     (unless (two-arg-char-not-lessp c (car list))
530       (return nil))))
531 \f
532 ;;;; miscellaneous functions
533
534 (defun char-upcase (char)
535   #!+sb-doc
536   "Return CHAR converted to upper-case if that is possible.  Don't convert
537    lowercase eszet (U+DF)."
538   (if (= (ucd-value-0 char) 1)
539       (code-char (ucd-value-1 char))
540       char))
541
542 (defun char-downcase (char)
543   #!+sb-doc
544   "Return CHAR converted to lower-case if that is possible."
545   (if (= (ucd-value-0 char) 0)
546       (code-char (ucd-value-1 char))
547       char))
548
549 (defun digit-char (weight &optional (radix 10))
550   #!+sb-doc
551   "All arguments must be integers. Returns a character object that
552   represents a digit of the given weight in the specified radix. Returns
553   NIL if no such character exists."
554   (and (typep weight 'fixnum)
555        (>= weight 0) (< weight radix) (< weight 36)
556        (code-char (if (< weight 10) (+ 48 weight) (+ 55 weight)))))