add GHC.HetMet.{hetmet_kappa,hetmet_kappa_app}
[ghc-base.git] / GHC / Unicode.hs
1 {-# LANGUAGE CPP, NoImplicitPrelude, ForeignFunctionInterface #-}
2 {-# OPTIONS -#include "WCsubst.h" #-}
3 {-# OPTIONS_HADDOCK hide #-}
4
5 -----------------------------------------------------------------------------
6 -- |
7 -- Module      :  GHC.Unicode
8 -- Copyright   :  (c) The University of Glasgow, 2003
9 -- License     :  see libraries/base/LICENSE
10 -- 
11 -- Maintainer  :  cvs-ghc@haskell.org
12 -- Stability   :  internal
13 -- Portability :  non-portable (GHC extensions)
14 --
15 -- Implementations for the character predicates (isLower, isUpper, etc.)
16 -- and the conversions (toUpper, toLower).  The implementation uses
17 -- libunicode on Unix systems if that is available.
18 --
19 -----------------------------------------------------------------------------
20
21 -- #hide
22 module GHC.Unicode (
23     isAscii, isLatin1, isControl,
24     isAsciiUpper, isAsciiLower,
25     isPrint, isSpace,  isUpper,
26     isLower, isAlpha,  isDigit,
27     isOctDigit, isHexDigit, isAlphaNum,
28     toUpper, toLower, toTitle,
29     wgencat,
30   ) where
31
32 import GHC.Base
33 import GHC.Real        (fromIntegral)
34 import Foreign.C.Types (CInt)
35
36 #include "HsBaseConfig.h"
37
38 -- | Selects the first 128 characters of the Unicode character set,
39 -- corresponding to the ASCII character set.
40 isAscii                 :: Char -> Bool
41 isAscii c               =  c <  '\x80'
42
43 -- | Selects the first 256 characters of the Unicode character set,
44 -- corresponding to the ISO 8859-1 (Latin-1) character set.
45 isLatin1                :: Char -> Bool
46 isLatin1 c              =  c <= '\xff'
47
48 -- | Selects ASCII lower-case letters,
49 -- i.e. characters satisfying both 'isAscii' and 'isLower'.
50 isAsciiLower :: Char -> Bool
51 isAsciiLower c          =  c >= 'a' && c <= 'z'
52
53 -- | Selects ASCII upper-case letters,
54 -- i.e. characters satisfying both 'isAscii' and 'isUpper'.
55 isAsciiUpper :: Char -> Bool
56 isAsciiUpper c          =  c >= 'A' && c <= 'Z'
57
58 -- | Selects control characters, which are the non-printing characters of
59 -- the Latin-1 subset of Unicode.
60 isControl               :: Char -> Bool
61
62 -- | Selects printable Unicode characters
63 -- (letters, numbers, marks, punctuation, symbols and spaces).
64 isPrint                 :: Char -> Bool
65
66 -- | Returns 'True' for any Unicode space character, and the control
67 -- characters @\\t@, @\\n@, @\\r@, @\\f@, @\\v@.
68 isSpace                 :: Char -> Bool
69 -- isSpace includes non-breaking space
70 -- Done with explicit equalities both for efficiency, and to avoid a tiresome
71 -- recursion with GHC.List elem
72 isSpace c               =  c == ' '     ||
73                            c == '\t'    ||
74                            c == '\n'    ||
75                            c == '\r'    ||
76                            c == '\f'    ||
77                            c == '\v'    ||
78                            c == '\xa0'  ||
79                            iswspace (fromIntegral (ord c)) /= 0
80
81 -- | Selects upper-case or title-case alphabetic Unicode characters (letters).
82 -- Title case is used by a small number of letter ligatures like the
83 -- single-character form of /Lj/.
84 isUpper                 :: Char -> Bool
85
86 -- | Selects lower-case alphabetic Unicode characters (letters).
87 isLower                 :: Char -> Bool
88
89 -- | Selects alphabetic Unicode characters (lower-case, upper-case and
90 -- title-case letters, plus letters of caseless scripts and modifiers letters).
91 -- This function is equivalent to 'Data.Char.isLetter'.
92 isAlpha                 :: Char -> Bool
93
94 -- | Selects alphabetic or numeric digit Unicode characters.
95 --
96 -- Note that numeric digits outside the ASCII range are selected by this
97 -- function but not by 'isDigit'.  Such digits may be part of identifiers
98 -- but are not used by the printer and reader to represent numbers.
99 isAlphaNum              :: Char -> Bool
100
101 -- | Selects ASCII digits, i.e. @\'0\'@..@\'9\'@.
102 isDigit                 :: Char -> Bool
103 isDigit c               =  c >= '0' && c <= '9'
104
105 -- | Selects ASCII octal digits, i.e. @\'0\'@..@\'7\'@.
106 isOctDigit              :: Char -> Bool
107 isOctDigit c            =  c >= '0' && c <= '7'
108
109 -- | Selects ASCII hexadecimal digits,
110 -- i.e. @\'0\'@..@\'9\'@, @\'a\'@..@\'f\'@, @\'A\'@..@\'F\'@.
111 isHexDigit              :: Char -> Bool
112 isHexDigit c            =  isDigit c || c >= 'A' && c <= 'F' ||
113                                         c >= 'a' && c <= 'f'
114
115 -- | Convert a letter to the corresponding upper-case letter, if any.
116 -- Any other character is returned unchanged.
117 toUpper                 :: Char -> Char
118
119 -- | Convert a letter to the corresponding lower-case letter, if any.
120 -- Any other character is returned unchanged.
121 toLower                 :: Char -> Char
122
123 -- | Convert a letter to the corresponding title-case or upper-case
124 -- letter, if any.  (Title case differs from upper case only for a small
125 -- number of ligature letters.)
126 -- Any other character is returned unchanged.
127 toTitle                 :: Char -> Char
128
129 -- -----------------------------------------------------------------------------
130 -- Implementation with the supplied auto-generated Unicode character properties
131 -- table (default)
132
133 #if 1
134
135 -- Regardless of the O/S and Library, use the functions contained in WCsubst.c
136
137 isAlpha    c = iswalpha (fromIntegral (ord c)) /= 0
138 isAlphaNum c = iswalnum (fromIntegral (ord c)) /= 0
139 --isSpace    c = iswspace (fromIntegral (ord c)) /= 0
140 isControl  c = iswcntrl (fromIntegral (ord c)) /= 0
141 isPrint    c = iswprint (fromIntegral (ord c)) /= 0
142 isUpper    c = iswupper (fromIntegral (ord c)) /= 0
143 isLower    c = iswlower (fromIntegral (ord c)) /= 0
144
145 toLower c = chr (fromIntegral (towlower (fromIntegral (ord c))))
146 toUpper c = chr (fromIntegral (towupper (fromIntegral (ord c))))
147 toTitle c = chr (fromIntegral (towtitle (fromIntegral (ord c))))
148
149 foreign import ccall unsafe "u_iswalpha"
150   iswalpha :: CInt -> CInt
151
152 foreign import ccall unsafe "u_iswalnum"
153   iswalnum :: CInt -> CInt
154
155 foreign import ccall unsafe "u_iswcntrl"
156   iswcntrl :: CInt -> CInt
157
158 foreign import ccall unsafe "u_iswspace"
159   iswspace :: CInt -> CInt
160
161 foreign import ccall unsafe "u_iswprint"
162   iswprint :: CInt -> CInt
163
164 foreign import ccall unsafe "u_iswlower"
165   iswlower :: CInt -> CInt
166
167 foreign import ccall unsafe "u_iswupper"
168   iswupper :: CInt -> CInt
169
170 foreign import ccall unsafe "u_towlower"
171   towlower :: CInt -> CInt
172
173 foreign import ccall unsafe "u_towupper"
174   towupper :: CInt -> CInt
175
176 foreign import ccall unsafe "u_towtitle"
177   towtitle :: CInt -> CInt
178
179 foreign import ccall unsafe "u_gencat"
180   wgencat :: CInt -> CInt
181
182 -- -----------------------------------------------------------------------------
183 -- No libunicode, so fall back to the ASCII-only implementation (never used, indeed)
184
185 #else
186
187 isControl c             =  c < ' ' || c >= '\DEL' && c <= '\x9f'
188 isPrint c               =  not (isControl c)
189
190 -- The upper case ISO characters have the multiplication sign dumped
191 -- randomly in the middle of the range.  Go figure.
192 isUpper c               =  c >= 'A' && c <= 'Z' ||
193                            c >= '\xC0' && c <= '\xD6' ||
194                            c >= '\xD8' && c <= '\xDE'
195 -- The lower case ISO characters have the division sign dumped
196 -- randomly in the middle of the range.  Go figure.
197 isLower c               =  c >= 'a' && c <= 'z' ||
198                            c >= '\xDF' && c <= '\xF6' ||
199                            c >= '\xF8' && c <= '\xFF'
200
201 isAlpha c               =  isLower c || isUpper c
202 isAlphaNum c            =  isAlpha c || isDigit c
203
204 -- Case-changing operations
205
206 toUpper c@(C# c#)
207   | isAsciiLower c    = C# (chr# (ord# c# -# 32#))
208   | isAscii c         = c
209     -- fall-through to the slower stuff.
210   | isLower c   && c /= '\xDF' && c /= '\xFF'
211   = unsafeChr (ord c `minusInt` ord 'a' `plusInt` ord 'A')
212   | otherwise
213   = c
214
215
216 toLower c@(C# c#)
217   | isAsciiUpper c = C# (chr# (ord# c# +# 32#))
218   | isAscii c      = c
219   | isUpper c      = unsafeChr (ord c `minusInt` ord 'A' `plusInt` ord 'a')
220   | otherwise      =  c
221
222 #endif
223