1 ;;;; character functions
3 ;;;; This software is part of the SBCL system. See the README file for
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.
12 (in-package "SB!IMPL")
14 ;;; We compile some trivial character operations via inline expansion.
16 (declaim (inline standard-char-p graphic-char-p alpha-char-p
17 upper-case-p lower-case-p both-case-p alphanumericp
))
18 (declaim (maybe-inline digit-char-p
))
21 `(integer 0 (,sb
!xc
:char-code-limit
)))
23 (defglobal **unicode-character-name-huffman-tree
** ())
25 (declaim (inline pack-3-codepoints
))
26 (defun pack-3-codepoints (first &optional
(second 0) (third 0))
27 (declare (type (unsigned-byte 21) first second third
))
28 (sb!c
::mask-signed-field
63 (logior first
(ash second
21) (ash third
42))))
30 (define-load-time-global **character-misc-database
** nil
)
31 (declaim (type (simple-array (unsigned-byte 8) (*)) **character-misc-database
**))
32 (declaim (inline both-case-index-p
))
33 (defun both-case-index-p (misc-index)
34 (declare (type (unsigned-byte 16) misc-index
))
35 (logbitp 7 (aref **character-misc-database
** (+ 5 misc-index
))))
38 (flet ((coerce-it (array)
39 (!coerce-to-specialized array
'(unsigned-byte 8)))
41 (merge-pathnames (make-pathname
43 '(:relative
:up
:up
"output")
44 :name name
:type type
)
45 sb
!xc
:*compile-file-truename
*))
46 (read-ub8-vector (pathname)
47 (with-open-file (stream pathname
48 :element-type
'(unsigned-byte 8))
49 (let* ((length (file-length stream
))
51 length
:element-type
'(unsigned-byte 8))))
52 (read-sequence array stream
)
54 (init-global (name type
)
57 ,(if (eql type
'hash-table
)
59 `(make-array 0 :element-type
',type
)))
60 (declaim (type ,(if (eql type
'hash-table
)
62 `(simple-array ,type
(*))) ,name
)))))
63 (let ((misc-database (coerce-it (read-ub8-vector (file "ucdmisc" "dat"))))
64 (ucd-high-pages (coerce-it (read-ub8-vector (file "ucdhigh" "dat"))))
65 (ucd-low-pages (coerce-it (read-ub8-vector (file "ucdlow" "dat"))))
66 (decompositions (coerce-it (read-ub8-vector (file "decomp" "dat"))))
67 (primary-compositions (coerce-it (read-ub8-vector (file "comp" "dat"))))
68 (case-data (coerce-it (read-ub8-vector (file "case" "dat"))))
69 (case-pages (coerce-it (read-ub8-vector (file "casepages" "dat"))))
70 (collations (coerce-it (read-ub8-vector (file "collation" "dat")))))
72 ;; KLUDGE: All temporary values, fixed up in cold-load
73 ,(init-global '**character-misc-database
** '(unsigned-byte 8))
74 ,(init-global '**character-high-pages
** '(unsigned-byte 16))
75 ,(init-global '**character-low-pages
** '(unsigned-byte 16))
76 ,(init-global '**character-decompositions
** '(unsigned-byte 21))
77 ,(init-global '**character-case-pages
** '(unsigned-byte 8))
78 ,(init-global '**character-primary-compositions
** 'hash-table
)
79 ,(init-global '**character-cases
** '(unsigned-byte 32))
80 ,(init-global '**character-unicode-cases
** t
)
81 ,(init-global '**character-collations
** 'hash-table
)
82 ,(init-global '**unicode-char-name-database
** t
)
83 ,(init-global '**unicode-name-char-database
** t
)
84 ,(init-global '**unicode-1-char-name-database
** t
)
85 ,(init-global '**unicode-1-name-char-database
** t
)
87 (defun !character-database-cold-init
()
88 (flet ((make-ubn-vector (raw-bytes n
)
91 (/ (length raw-bytes
) n
)
92 :element-type
(list 'unsigned-byte
(* 8 n
)))))
93 (loop for i from
0 below
(length raw-bytes
) by n
95 (loop for offset from
0 below n do
97 (ash (aref raw-bytes
(+ i offset
))
98 (* 8 (- n offset
1)))))
99 (setf (aref new-array
(/ i n
)) element
))
101 (setf **character-misc-database
**
103 **character-high-pages
**
104 (make-ubn-vector ,ucd-high-pages
2)
105 **character-low-pages
**
106 (make-ubn-vector ,ucd-low-pages
2)
107 **character-case-pages
**
108 ,(coerce-it case-pages
)
109 **character-decompositions
**
110 (make-ubn-vector ,decompositions
3))
112 (setf **character-primary-compositions
**
113 (let ((table (make-hash-table))
114 (info (make-ubn-vector ,primary-compositions
3)))
115 (dotimes (i (/ (length info
) 3))
116 (setf (gethash (dpb (aref info
(* 3 i
)) (byte 21 21)
117 (aref info
(1+ (* 3 i
))))
119 (aref info
(+ (* 3 i
) 2))))
122 (let* ((unicode-table
124 (* 64 (1+ (aref **character-case-pages
**
125 (1- (length **character-case-pages
**)))))))
127 (* 2 (length unicode-table
))
128 :element-type
'(unsigned-byte 32)))
131 (length (length info
)))
132 (labels ((read-codepoint ()
133 (let* ((b1 (aref info index
))
134 (b2 (aref info
(incf index
)))
135 (b3 (aref info
(incf index
))))
138 (dpb b2
(byte 8 8) b3
))))
139 (read-length-tagged ()
140 (let ((len (aref info index
)) ret
)
146 (push (read-codepoint) ret
))
148 (loop until
(>= index length
)
149 for key
= (read-codepoint)
150 for upper
= (read-length-tagged)
151 for lower
= (read-length-tagged)
152 for page
= (aref **character-case-pages
** (ash key -
6))
153 for i
= (+ (ash page
6) (ldb (byte 6 0) key
))
155 (setf (aref unicode-table i
) (cons upper lower
))
156 when
(and (atom upper
)
158 ;; Some characters are only equal under unicode rules,
159 ;; e.g. #\MICRO_SIGN and #\GREEK_CAPITAL_LETTER_MU
161 (both-case-index-p (misc-index (code-char lower
)))
163 (both-case-index-p (misc-index (code-char upper
))))
165 (setf (aref table
(* i
2)) lower
166 (aref table
(1+ (* i
2))) upper
)))
167 (setf **character-unicode-cases
** unicode-table
)
168 (setf **character-cases
** table
))
170 (setf **character-collations
**
171 (let* ((table (make-hash-table))
173 (info (make-ubn-vector ,collations
4))
175 (loop while
(< index len
) do
176 (let* ((entry-head (aref info index
))
177 (cp-length (ldb (byte 4 28) entry-head
))
178 (key-length (ldb (byte 5 23) entry-head
))
181 :element-type
'(unsigned-byte 32)))
183 (assert (and (/= cp-length
0) (/= key-length
0)))
184 (loop repeat cp-length do
185 (push (dpb 0 (byte 10 22) (aref info index
))
188 (setf codepoints
(nreverse codepoints
))
189 (dotimes (i key-length
)
190 (setf (aref key i
) (aref info index
))
193 (apply #'pack-3-codepoints codepoints
)
198 (stream (file "ucd-names" "lisp-expr"))
199 (with-open-file (u1-stream (file "ucd1-names" "lisp-expr"))
200 (flet ((convert-to-double-vector (vector &optional reversed
)
201 (let ((result (make-array (* (length vector
) 2))))
202 (loop for
(code . name
) across vector
207 (setf (aref result i
) code
208 (aref result
(1+ i
)) name
))
210 (let ((names (make-hash-table))
211 (u1-names (make-hash-table)))
213 for code-point
= (read stream nil nil
)
214 for char-name
= (string-upcase (read stream nil nil
))
216 do
(setf (gethash code-point names
) char-name
))
218 for code-point
= (read u1-stream nil nil
)
219 for char-name
= (string-upcase (read u1-stream nil nil
))
221 do
(setf (gethash code-point u1-names
) char-name
))
225 (maphash (lambda (code name
)
226 (declare (ignore code
))
229 (maphash (lambda (code u1-name
)
230 (declare (ignore code
))
235 (make-array (hash-table-count names
)
239 (make-array (hash-table-count u1-names
)
242 (maphash (lambda (code name
)
244 (cons code
(huffman-encode name tree
))
247 (maphash (lambda (code name
)
249 (cons code
(huffman-encode name tree
))
253 (sort (copy-seq code-
>name
) #'< :key
#'cdr
))
255 (sort (copy-seq name-
>code
) #'< :key
#'car
))
257 (sort (copy-seq code-
>u1-name
) #'< :key
#'cdr
))
259 (sort (copy-seq u1-name-
>code
) #'< :key
#'car
))
260 (setf names nil u1-names nil
)
261 `(defun !character-name-database-cold-init
()
262 (setf **unicode-character-name-huffman-tree
** ',tree
263 **unicode-char-name-database
**
264 ',(convert-to-double-vector code-
>name
)
265 **unicode-name-char-database
**
266 ',(convert-to-double-vector name-
>code t
)
267 **unicode-1-char-name-database
**
268 ',(convert-to-double-vector code-
>u1-name
)
269 **unicode-1-name-char-database
**
270 ',(convert-to-double-vector u1-name-
>code t
)))))))))))))
273 #+sb-xc-host
(!character-name-database-cold-init
)
275 (defparameter *base-char-name-alist
*
276 ;; Note: The *** markers here indicate character names which are
277 ;; required by the ANSI specification of #'CHAR-NAME. For the others,
278 ;; we prefer the ASCII standard name.
279 '((#x00
"Nul" "Null" "^@")
286 ;; Don't alias to Bell, another Unicode character has that name.
288 (#x08
"Backspace" "^h" "Bs") ; *** See Note above
289 (#x09
"Tab" "^i" "Ht") ; *** See Note above
290 (#x0A
"Newline" "Linefeed" "^j" "Lf" "Nl") ; *** See Note above
292 (#x0C
"Page" "^l" "Form" "Formfeed" "Ff" "Np") ; *** See Note above
293 (#x0D
"Return" "^m" "Cr") ; *** See Note above
307 (#x1B
"Esc" "Escape" "^[" "Altmode" "Alt")
312 (#x20
"Space" "Sp") ; *** See Note above
313 (#x7f
"Rubout" "Delete" "Del")
316 (#x82
"Break-Permitted")
317 (#x83
"No-Break-Permitted")
320 (#x86
"Start-Selected-Area")
321 (#x87
"End-Selected-Area")
322 (#x88
"Character-Tabulation-Set")
323 (#x89
"Character-Tabulation-With-Justification")
324 (#x8A
"Line-Tabulation-Set")
325 (#x8B
"Partial-Line-Forward")
326 (#x8C
"Partial-Line-Backward")
327 (#x8D
"Reverse-Linefeed")
328 (#x8E
"Single-Shift-Two")
329 (#x8F
"Single-Shift-Three")
330 (#x90
"Device-Control-String")
331 (#x91
"Private-Use-One")
332 (#x92
"Private-Use-Two")
333 (#x93
"Set-Transmit-State")
334 (#x94
"Cancel-Character")
335 (#x95
"Message-Waiting")
336 (#x96
"Start-Guarded-Area")
337 (#x97
"End-Guarded-Area")
338 (#x98
"Start-String")
340 (#x9A
"Single-Character-Introducer")
341 (#x9B
"Control-Sequence-Introducer")
342 (#x9C
"String-Terminator")
343 (#x9D
"Operating-System-Command")
344 (#x9E
"Privacy-Message")
345 (#x9F
"Application-Program-Command"))) ; *** See Note above
347 ;;;; UCD accessor functions
349 ;;; The character database is made of several arrays.
350 ;;; **CHARACTER-MISC-DATABASE** is an array of bytes that encode character
351 ;;; attributes. Each entry in the misc database is +misc-width+ (currently 8)
352 ;;; bytes wide. Within each entry, the bytes represent: general category, BIDI
353 ;;; class, canonical combining class, digit value, decomposition info, other
354 ;;; flags, script, line break class, and age, respectively. Several of the
355 ;;; entries have additional information encoded in them at the bit level. The
356 ;;; digit value field is equal to 128 (has only its high bit set) if characters
357 ;;; with that set of attribute are not digits. Bit 6 is set if that entry
358 ;;; encodes decimal digits, that is, characters that are DIGIT-CHAR-P. The rest
359 ;;; of the value is the digit value of characters with that entry. Decomposition
360 ;;; info contains the length of the decomposition of characters with that entry,
361 ;;; and also sets its high bit if the decompositions are compatibility
362 ;;; decompositions. The other flags byte encodes boolean properties. Bit 7 is
363 ;;; set if the entry's characters are BOTH-CASE-P in the Common Lisp sense. Bit
364 ;;; 6 is set if the entry's characters hav a defined case transformation in
365 ;;; Unicode. Bit 5 is set if the characters have the property BIDI_Mirrored=Y.
366 ;;; Bits 3-0 encode the entry's East Asian Width. Bit 4 is unused. Age stores
367 ;;; the minor version in bits 0-2, and the major version in the remaining 5
370 ;;; To find which entry in **CHARACTER-MISC-DATABASE** encodes a character's
371 ;;; attributes, first index **CHARACTER-HIGH-PAGES** (an array of 16-bit
372 ;;; values) with the high 13 bits of the character's codepoint. If the result
373 ;;; value has its high bit set, the character is in a "compressed page". To
374 ;;; find the misc entry number, simply clear the high bit. If the high bit is
375 ;;; not set, the misc entry number must be looked up in
376 ;;; **CHARACTER-LOW-PAGES**, which is an array of 16-bit values. Each entry in
377 ;;; the array consists of two such values, the misc entry number and the
378 ;;; decomposition index. To find the misc entry number, index into
379 ;;; **CHARACTER-LOW-PAGES** using the value retreived from
380 ;;; **CHARACTER-HIGH-PAGES** (shifted left 8 bits) plus the low 8 bits of the
381 ;;; codepoint, all times two to account for the widtth of the entries. The
382 ;;; value in **CHARACTER-LOW-PAGES** at this point is the misc entry number. To
383 ;;; transform a misc entry number into an index into
384 ;;; **CHARACTER-MISC-DATABASE**, multiply it by +misc-width*. This gives the
385 ;;; index of the start of the charater's misc entry in
386 ;;; **CHARACTER-MISC-DATABASE**.
388 ;;; To look up a character's decomposition, first retreive its
389 ;;; decomposition-info from the misc database as described above. If the
390 ;;; decomposition info is not 0, the character has a decomposition with a
391 ;;; length given by the decomposition info with the high bit (which indicates
392 ;;; compatibility/canonical status) cleared. To find the decomposition, move
393 ;;; one value past the character's misc entry number in
394 ;;; **CHARACTER-LOW-DATABASE**, which gives an index into
395 ;;; **CHARACTER-DECOMPOSITIONS**. The next LENGTH values in
396 ;;; **CHARACTER-DECOMPOSITIONS** (an array of codepoints), starting at this
397 ;;; index, are the decomposition of the character. This proceduce does not
398 ;;; apply to Hangul syllables, which have their own decomposition algorithm.
400 ;;; Case information is stored in **CHARACTER-UNICODE-CASES**, an array that
401 ;;; indirectly maps a character's codepoint to (cons uppercase
402 ;;; lowercase). Uppercase and lowercase are either a single codepoint,
403 ;;; which is the upper- or lower-case of the given character, or a
404 ;;; list of codepoints which taken as a whole are the upper- or
405 ;;; lower-case. These case lists are only used in Unicode case
406 ;;; transformations, not in Common Lisp ones.
408 ;;; **CHARACTER-CASES** is similar to the above but it stores codes in
409 ;;; a flat array twice as large, and it includes only the standard casing rules,
410 ;;; so there's always just two characters.
412 ;;; Similarly, composition information is stored in **CHARACTER-COMPOSITIONS**,
413 ;;; which is a hash table of codepoints indexed by (+ (ash codepoint1 21)
416 (declaim (inline clear-flag
))
417 (defun clear-flag (bit integer
)
418 (logandc2 integer
(ash 1 bit
)))
420 (defconstant +misc-width
+ 9)
422 (declaim (ftype (sfunction (t) (unsigned-byte 16)) misc-index
))
423 (defun misc-index (char)
424 (let* ((cp (char-code char
))
425 (cp-high (ash cp -
8))
426 (high-index (aref **character-high-pages
** cp-high
)))
427 (if (logbitp 15 high-index
)
428 (* +misc-width
+ (clear-flag 15 high-index
))
430 (aref **character-low-pages
**
431 (* 2 (+ (ldb (byte 8 0) cp
) (ash high-index
8))))))))
433 (declaim (ftype (sfunction (t) (unsigned-byte 8)) ucd-general-category
)
434 (inline ucd-general-category
))
435 (defun ucd-general-category (char)
436 (aref **character-misc-database
** (misc-index char
)))
438 (defun ucd-decimal-digit (char)
439 (let ((digit (aref **character-misc-database
**
440 (+ 3 (misc-index char
)))))
441 (when (logbitp 6 digit
) ; decimalp flag
442 (ldb (byte 4 0) digit
))))
444 (defun char-code (char)
446 "Return the integer code of CHAR."
449 (defun char-int (char)
451 "Return the integer code of CHAR. (In SBCL this is the same as CHAR-CODE, as
452 there are no character bits or fonts.)"
455 (defun code-char (code)
457 "Return the character with the code CODE."
460 (defun character (object)
462 "Coerce OBJECT into a CHARACTER if possible. Legal inputs are characters,
463 strings and symbols of length 1."
464 (flet ((do-error (control args
)
465 (declare (optimize allow-non-returning-tail-call
))
466 (error 'simple-type-error
468 ;;?? how to express "symbol with name of length 1"?
469 :expected-type
'(or character
(string 1))
470 :format-control control
471 :format-arguments args
)))
474 (string (if (= 1 (length (the string object
)))
477 "String is not of length one: ~S" (list object
))))
478 (symbol (if (= 1 (length (symbol-name object
)))
479 (schar (symbol-name object
) 0)
481 "Symbol name is not of length one: ~S" (list object
))))
482 (t (do-error "~S cannot be coerced to a character." (list object
))))))
484 (defun char-name (char)
486 "Return the name (a STRING) for a CHARACTER object."
487 (let ((char-code (char-code char
)))
488 (or (second (assoc char-code
*base-char-name-alist
*))
489 (let ((h-code (double-vector-binary-search char-code
490 **unicode-char-name-database
**)))
493 (huffman-decode h-code
**unicode-character-name-huffman-tree
**))
495 (format nil
"U~X" char-code
)))))))
497 (defun name-char (name)
499 "Given an argument acceptable to STRING, NAME-CHAR returns a character whose
500 name is that string, if one exists. Otherwise, NIL is returned."
501 (let ((char-code (car (rassoc-if (lambda (names)
502 (member name names
:test
#'string-equal
))
503 *base-char-name-alist
*))))
505 (code-char char-code
))
506 ((let ((start (cond ((eql (string-not-equal "U+" name
) 2)
508 ((eql (string-not-equal "U" name
) 1)
511 (loop for i from start
513 always
(digit-char-p (char name i
) 16))
514 (code-char (parse-integer name
:start start
:radix
16)))))
516 (let ((encoding (huffman-encode (string-upcase name
)
517 **unicode-character-name-huffman-tree
**)))
521 (double-vector-binary-search encoding
522 **unicode-name-char-database
**)
523 (double-vector-binary-search encoding
524 **unicode-1-name-char-database
**))))
526 (code-char char-code
)))))))))
530 (defun standard-char-p (char)
532 "The argument must be a character object. STANDARD-CHAR-P returns T if the
533 argument is a standard character -- one of the 95 ASCII printing characters or
535 (and (typep char
'base-char
)
536 (let ((n (char-code (the base-char char
))))
540 (defun %standard-char-p
(thing)
542 "Return T if and only if THING is a standard-char. Differs from
543 STANDARD-CHAR-P in that THING doesn't have to be a character."
544 (and (characterp thing
) (standard-char-p thing
)))
546 (defun graphic-char-p (char)
548 "The argument must be a character object. GRAPHIC-CHAR-P returns T if the
549 argument is a printing character (space through ~ in ASCII), otherwise returns
551 (let ((n (char-code char
)))
555 (defun alpha-char-p (char)
557 "The argument must be a character object. ALPHA-CHAR-P returns T if the
558 argument is an alphabetic character, A-Z or a-z; otherwise NIL."
559 (< (ucd-general-category char
) 5))
561 (defun both-case-p (char)
563 "The argument must be a character object. BOTH-CASE-P returns T if the
564 argument is an alphabetic character and if the character exists in both upper
565 and lower case. For ASCII, this is the same as ALPHA-CHAR-P."
566 (both-case-index-p (misc-index char
)))
568 (defun upper-case-p (char)
570 "The argument must be a character object; UPPER-CASE-P returns T if the
571 argument is an upper-case character, NIL otherwise."
572 (let ((index (misc-index char
)))
574 (both-case-index-p index
)
575 (= (aref **character-misc-database
** index
) 0))))
577 (defun lower-case-p (char)
579 "The argument must be a character object; LOWER-CASE-P returns T if the
580 argument is a lower-case character, NIL otherwise."
581 (let ((index (misc-index char
)))
583 (both-case-index-p index
)
584 (= (aref **character-misc-database
** index
) 1))))
586 (defun digit-char-p (char &optional
(radix 10.
))
588 "If char is a digit in the specified radix, returns the fixnum for which
589 that digit stands, else returns NIL."
590 (if (<= (char-code char
) 127)
591 (let ((weight (- (char-code char
) 48)))
592 (cond ((minusp weight
) nil
)
594 ;; Special-case ASCII digits in decimal and smaller radices.
595 (if (< weight radix
) weight nil
))
596 ;; Digits 0 - 9 are used as is, since radix is larger.
597 ((< weight
10) weight
)
598 ;; Check for upper case A - Z.
599 ((and (>= (decf weight
7) 10) (< weight radix
)) weight
)
600 ;; Also check lower case a - z.
601 ((and (>= (decf weight
32) 10) (< weight radix
)) weight
)))
602 (let ((number (ucd-decimal-digit char
)))
603 (when (and number
(< (truly-the fixnum number
) radix
))
606 (defun alphanumericp (char)
608 "Given a character-object argument, ALPHANUMERICP returns T if the argument
609 is either numeric or alphabetic."
610 (let ((gc (ucd-general-category char
)))
614 ;;; EQUAL-CHAR-CODE is used by the following functions as a version of CHAR-INT
615 ;;; which loses font, bits, and case info.
617 ;;; Return a cons with (upper-case . lower-case), where it either can
618 ;;; be a character code or a list of character codes if the character
619 ;;; donwcases or upcases into multiple characters.
620 (declaim (inline char-case-info
))
621 (defun char-case-info (character)
622 (let* ((code (char-code character
))
623 (page (aref **character-case-pages
** (ash code -
6))))
624 ;; Pages with 255 means the character is not both-case.
625 ;; **character-cases** has 0 for those characters.
626 (aref **character-unicode-cases
**
628 (ldb (byte 6 0) code
)))))
630 ;;; Returns the downcased code or the character code
631 (declaim (inline equal-char-code
))
632 (defun equal-char-code (char)
633 (let* ((code (char-code char
))
634 (shifted (ash code -
6))
635 (page (if (>= shifted
(length **character-case-pages
**))
636 (return-from equal-char-code code
)
637 (aref **character-case-pages
** shifted
))))
641 (aref **character-cases
**
643 (ldb (byte 6 0) code
))
645 (if (zerop down-code
)
649 (defun two-arg-char-equal (c1 c2
)
650 (flet ((base-char-equal-p ()
651 (let* ((code1 (char-code c1
))
652 (code2 (char-code c2
))
653 (sum (logxor code1 code2
)))
655 (let ((sum (+ code1 code2
)))
656 (or (and (< 161 sum
213))
657 (and (< 415 sum
461))
658 (and (< 463 sum
477))))))))
659 (declare (inline base-char-equal-p
))
666 (and (base-char-p c2
)
667 (base-char-equal-p)))
669 (= (equal-char-code c1
) (equal-char-code c2
)))))))
671 (defun char-equal-constant (x char reverse-case-char
)
672 (declare (type character x
) (explicit-check))
674 (eq reverse-case-char x
)))
676 (defun two-arg-char-not-equal (c1 c2
)
677 (/= (equal-char-code c1
) (equal-char-code c2
)))
679 (macrolet ((def (name test doc
)
680 (declare (ignorable doc
))
681 `(defun ,name
(character &rest more-characters
)
684 (do ((c character
(nth i more-characters
))
686 ((>= i
(length more-characters
)) t
)
687 (do-rest-arg ((c2) more-characters i
)
689 (return-from ,name nil
))))
690 ;; CHAR-NOT-EQUAL has explicit check attribute
691 (progn (the character character
) t
)))))
692 (def char
/= (eq c
(the character c2
))
693 "Return T if no two of the arguments are the same character.")
694 (def char-not-equal
(two-arg-char-equal c c2
)
695 "Return T if no two of the arguments are the same character.
698 (defun two-arg-char-lessp (c1 c2
)
699 (< (equal-char-code c1
) (equal-char-code c2
)))
701 (defun two-arg-char-greaterp (c1 c2
)
702 (> (equal-char-code c1
) (equal-char-code c2
)))
704 (defun two-arg-char-not-greaterp (c1 c2
)
705 (<= (equal-char-code c1
) (equal-char-code c2
)))
707 (defun two-arg-char-not-lessp (c1 c2
)
708 (>= (equal-char-code c1
) (equal-char-code c2
)))
710 (macrolet ((def (op test doc
&optional explicit-check
)
711 (declare (ignorable doc
))
712 `(defun ,op
(character &rest more-characters
)
714 ,@(when explicit-check
`((declare (explicit-check))))
715 (let ((c1 character
))
716 (declare (character c1
))
717 (do-rest-arg ((c2 i
) more-characters
0 t
)
720 (return (do-rest-arg ((c) more-characters
(1+ i
))
721 (the character c
))))))))) ; for effect
723 (def char
= (eq c1
(the character c2
))
724 "Return T if all of the arguments are the same character.")
725 (def char
< (< (char-int c1
) (char-int c2
))
726 "Return T if the arguments are in strictly increasing alphabetic order.")
727 (def char
> (> (char-int c1
) (char-int c2
))
728 "Return T if the arguments are in strictly decreasing alphabetic order.")
729 (def char
<= (<= (char-int c1
) (char-int c2
))
730 "Return T if the arguments are in strictly non-decreasing alphabetic order.")
731 (def char
>= (>= (char-int c1
) (char-int c2
))
732 "Return T if the arguments are in strictly non-increasing alphabetic order.")
735 (def char-equal
(two-arg-char-equal c1 c2
)
736 "Return T if all of the arguments are the same character.
738 (def char-lessp
(two-arg-char-lessp c1 c2
)
739 "Return T if the arguments are in strictly increasing alphabetic order.
741 (def char-greaterp
(two-arg-char-greaterp c1 c2
)
742 "Return T if the arguments are in strictly decreasing alphabetic order.
744 (def char-not-greaterp
(two-arg-char-not-greaterp c1 c2
)
745 "Return T if the arguments are in strictly non-decreasing alphabetic order.
747 (def char-not-lessp
(two-arg-char-not-lessp c1 c2
)
748 "Return T if the arguments are in strictly non-increasing alphabetic order.
749 Case is ignored." t
))
752 ;;;; miscellaneous functions
754 (defun char-upcase (char)
756 "Return CHAR converted to upper-case if that is possible. Don't convert
757 lowercase eszet (U+DF)."
758 (let* ((code (char-code char
))
759 (shifted (ash code -
6))
760 (page (if (>= shifted
(length **character-case-pages
**))
761 (return-from char-upcase char
)
762 (aref **character-case-pages
** shifted
))))
766 (aref **character-cases
**
767 (1+ (* (+ (ash page
6)
768 (ldb (byte 6 0) code
))
772 (code-char code
))))))
774 (defun char-downcase (char)
776 "Return CHAR converted to lower-case if that is possible."
777 (let* ((code (char-code char
))
778 (shifted (ash code -
6))
779 (page (if (< shifted
(length **character-case-pages
**))
780 (aref **character-case-pages
** shifted
)
781 (return-from char-downcase char
))))
785 (aref **character-cases
**
787 (ldb (byte 6 0) code
))))))
790 (code-char code
))))))
792 (defun digit-char (weight &optional
(radix 10))
794 "All arguments must be integers. Returns a character object that represents
795 a digit of the given weight in the specified radix. Returns NIL if no such
797 (and (typep weight
'fixnum
)
798 (>= weight
0) (< weight radix
) (< weight
36)
799 (code-char (if (< weight
10) (+ 48 weight
) (+ 55 weight
)))))
801 ;;; Moved from 'string' because ALPHANUMERICP wants to be inlined,
802 ;;; and moving ALPHANUMERICP earlier causes a snowball effect of
803 ;;; other inlining failures.
804 (flet ((%capitalize
(string start end
)
805 (declare (string string
) (index start
) (type sequence-end end
))
806 (let ((saved-header string
))
807 (with-one-string (string start end
)
808 (do ((index start
(1+ index
))
811 ((= index
(the fixnum end
)))
812 (declare (fixnum index
))
813 (setq char
(schar string index
))
814 (cond ((not (alphanumericp char
))
817 ;; CHAR is the first case-modifiable character after
818 ;; a sequence of non-case-modifiable characters.
819 (setf (schar string index
) (char-upcase char
))
820 (setq new-word? nil
))
822 (setf (schar string index
) (char-downcase char
))))))
824 (defun string-capitalize (string &key
(start 0) end
)
825 (%capitalize
(copy-seq (string string
)) start end
))
826 (defun nstring-capitalize (string &key
(start 0) end
)
827 (%capitalize string start end
))