1 {-# LANGUAGE CPP, NoImplicitPrelude #-}
3 -----------------------------------------------------------------------------
6 -- Copyright : (c) The University of Glasgow 2001
7 -- License : BSD-style (see the file libraries/base/LICENSE)
9 -- Maintainer : libraries@haskell.org
11 -- Portability : portable
13 -- The Char type and associated operations.
15 -----------------------------------------------------------------------------
21 -- * Character classification
22 -- | Unicode characters are divided into letters, numbers, marks,
23 -- punctuation, symbols, separators (including spaces) and others
24 -- (including control characters).
26 , isLower, isUpper, isAlpha, isAlphaNum, isPrint
27 , isDigit, isOctDigit, isHexDigit
28 , isLetter, isMark, isNumber, isPunctuation, isSymbol, isSeparator
32 , isAsciiUpper, isAsciiLower
34 -- ** Unicode general categories
35 , GeneralCategory(..), generalCategory
38 , toUpper, toLower, toTitle -- :: Char -> Char
40 -- * Single digit characters
41 , digitToInt -- :: Char -> Int
42 , intToDigit -- :: Int -> Char
44 -- * Numeric representations
45 , ord -- :: Char -> Int
46 , chr -- :: Int -> Char
48 -- * String representations
49 , showLitChar -- :: Char -> ShowS
50 , lexLitChar -- :: ReadS String
51 , readLitChar -- :: ReadS Char
53 -- Implementation checked wrt. Haskell 98 lib report, 1/99.
56 #ifdef __GLASGOW_HASKELL__
59 import GHC.Real (fromIntegral)
61 import GHC.Read (Read, readLitChar, lexLitChar)
68 import Hugs.Prelude (Ix)
74 import Prelude(Char,String)
78 foreign import ccall unsafe "WCsubst.h u_gencat" wgencat :: CInt -> CInt
81 -- | Convert a single digit 'Char' to the corresponding 'Int'.
82 -- This function fails unless its argument satisfies 'isHexDigit',
83 -- but recognises both upper and lower-case hexadecimal digits
84 -- (i.e. @\'0\'@..@\'9\'@, @\'a\'@..@\'f\'@, @\'A\'@..@\'F\'@).
85 digitToInt :: Char -> Int
87 | isDigit c = ord c - ord '0'
88 | c >= 'a' && c <= 'f' = ord c - ord 'a' + 10
89 | c >= 'A' && c <= 'F' = ord c - ord 'A' + 10
90 | otherwise = error ("Char.digitToInt: not a digit " ++ show c) -- sigh
92 #ifndef __GLASGOW_HASKELL__
93 isAsciiUpper, isAsciiLower :: Char -> Bool
94 isAsciiLower c = c >= 'a' && c <= 'z'
95 isAsciiUpper c = c >= 'A' && c <= 'Z'
98 -- | Unicode General Categories (column 2 of the UnicodeData table)
99 -- in the order they are listed in the Unicode standard.
102 = UppercaseLetter -- ^ Lu: Letter, Uppercase
103 | LowercaseLetter -- ^ Ll: Letter, Lowercase
104 | TitlecaseLetter -- ^ Lt: Letter, Titlecase
105 | ModifierLetter -- ^ Lm: Letter, Modifier
106 | OtherLetter -- ^ Lo: Letter, Other
107 | NonSpacingMark -- ^ Mn: Mark, Non-Spacing
108 | SpacingCombiningMark -- ^ Mc: Mark, Spacing Combining
109 | EnclosingMark -- ^ Me: Mark, Enclosing
110 | DecimalNumber -- ^ Nd: Number, Decimal
111 | LetterNumber -- ^ Nl: Number, Letter
112 | OtherNumber -- ^ No: Number, Other
113 | ConnectorPunctuation -- ^ Pc: Punctuation, Connector
114 | DashPunctuation -- ^ Pd: Punctuation, Dash
115 | OpenPunctuation -- ^ Ps: Punctuation, Open
116 | ClosePunctuation -- ^ Pe: Punctuation, Close
117 | InitialQuote -- ^ Pi: Punctuation, Initial quote
118 | FinalQuote -- ^ Pf: Punctuation, Final quote
119 | OtherPunctuation -- ^ Po: Punctuation, Other
120 | MathSymbol -- ^ Sm: Symbol, Math
121 | CurrencySymbol -- ^ Sc: Symbol, Currency
122 | ModifierSymbol -- ^ Sk: Symbol, Modifier
123 | OtherSymbol -- ^ So: Symbol, Other
124 | Space -- ^ Zs: Separator, Space
125 | LineSeparator -- ^ Zl: Separator, Line
126 | ParagraphSeparator -- ^ Zp: Separator, Paragraph
127 | Control -- ^ Cc: Other, Control
128 | Format -- ^ Cf: Other, Format
129 | Surrogate -- ^ Cs: Other, Surrogate
130 | PrivateUse -- ^ Co: Other, Private Use
131 | NotAssigned -- ^ Cn: Other, Not Assigned
132 deriving (Eq, Ord, Enum, Read, Show, Bounded, Ix)
134 -- | The Unicode general category of the character.
135 generalCategory :: Char -> GeneralCategory
136 #if defined(__GLASGOW_HASKELL__) || defined(__NHC__)
137 generalCategory c = toEnum $ fromIntegral $ wgencat $ fromIntegral $ ord c
140 generalCategory c = toEnum (primUniGenCat c)
143 -- derived character classifiers
145 -- | Selects alphabetic Unicode characters (lower-case, upper-case and
146 -- title-case letters, plus letters of caseless scripts and modifiers letters).
147 -- This function is equivalent to 'Data.Char.isAlpha'.
148 isLetter :: Char -> Bool
149 isLetter c = case generalCategory c of
150 UppercaseLetter -> True
151 LowercaseLetter -> True
152 TitlecaseLetter -> True
153 ModifierLetter -> True
157 -- | Selects Unicode mark characters, e.g. accents and the like, which
158 -- combine with preceding letters.
159 isMark :: Char -> Bool
160 isMark c = case generalCategory c of
161 NonSpacingMark -> True
162 SpacingCombiningMark -> True
163 EnclosingMark -> True
166 -- | Selects Unicode numeric characters, including digits from various
167 -- scripts, Roman numerals, etc.
168 isNumber :: Char -> Bool
169 isNumber c = case generalCategory c of
170 DecimalNumber -> True
175 -- | Selects Unicode punctuation characters, including various kinds
176 -- of connectors, brackets and quotes.
177 isPunctuation :: Char -> Bool
178 isPunctuation c = case generalCategory c of
179 ConnectorPunctuation -> True
180 DashPunctuation -> True
181 OpenPunctuation -> True
182 ClosePunctuation -> True
185 OtherPunctuation -> True
188 -- | Selects Unicode symbol characters, including mathematical and
190 isSymbol :: Char -> Bool
191 isSymbol c = case generalCategory c of
193 CurrencySymbol -> True
194 ModifierSymbol -> True
198 -- | Selects Unicode space and separator characters.
199 isSeparator :: Char -> Bool
200 isSeparator c = case generalCategory c of
202 LineSeparator -> True
203 ParagraphSeparator -> True
207 -- dummy implementation
208 toTitle :: Char -> Char