data Char |
To convert a Char to or from the corresponding Int value defined by Unicode, use Prelude.toEnum and Prelude.fromEnum from the Prelude.Enum class respectively (or equivalently ord and chr).
instance Bounded Char |
instance Enum Char |
instance Eq Char |
instance Ord Char |
instance Read Char |
instance Show Char |
instance Ix Char |
instance Storable Char |
type String = [Char] |
Unicode characters are divided into letters, numbers, marks, punctuation, symbols, separators (including spaces) and others (including control characters).
isControl :: Char -> Bool |
isSpace :: Char -> Bool |
isLower :: Char -> Bool |
isUpper :: Char -> Bool |
isAlpha :: Char -> Bool |
isAlphaNum :: Char -> Bool |
Note that numeric digits outside the ASCII range are selected by this function but not by isDigit. Such digits may be part of identifiers but are not used by the printer and reader to represent numbers.
isPrint :: Char -> Bool |
isDigit :: Char -> Bool |
isOctDigit :: Char -> Bool |
isHexDigit :: Char -> Bool |
isLetter :: Char -> Bool |
isMark :: Char -> Bool |
isNumber :: Char -> Bool |
isPunctuation :: Char -> Bool |
isSymbol :: Char -> Bool |
isSeparator :: Char -> Bool |
isAscii :: Char -> Bool |
isLatin1 :: Char -> Bool |
isAsciiUpper :: Char -> Bool |
isAsciiLower :: Char -> Bool |
data GeneralCategory |
= | UppercaseLetter | Lu: Letter, Uppercase |
| | LowercaseLetter | Ll: Letter, Lowercase |
| | TitlecaseLetter | Lt: Letter, Titlecase |
| | ModifierLetter | Lm: Letter, Modifier |
| | OtherLetter | Lo: Letter, Other |
| | NonSpacingMark | Mn: Mark, Non-Spacing |
| | SpacingCombiningMark | Mc: Mark, Spacing Combining |
| | EnclosingMark | Me: Mark, Enclosing |
| | DecimalNumber | Nd: Number, Decimal |
| | LetterNumber | Nl: Number, Letter |
| | OtherNumber | No: Number, Other |
| | ConnectorPunctuation | Pc: Punctuation, Connector |
| | DashPunctuation | Pd: Punctuation, Dash |
| | OpenPunctuation | Ps: Punctuation, Open |
| | ClosePunctuation | Pe: Punctuation, Close |
| | InitialQuote | Pi: Punctuation, Initial quote |
| | FinalQuote | Pf: Punctuation, Final quote |
| | OtherPunctuation | Po: Punctuation, Other |
| | MathSymbol | Sm: Symbol, Math |
| | CurrencySymbol | Sc: Symbol, Currency |
| | ModifierSymbol | Sk: Symbol, Modifier |
| | OtherSymbol | So: Symbol, Other |
| | Space | Zs: Separator, Space |
| | LineSeparator | Zl: Separator, Line |
| | ParagraphSeparator | Zp: Separator, Paragraph |
| | Control | Cc: Other, Control |
| | Format | Cf: Other, Format |
| | Surrogate | Cs: Other, Surrogate |
| | PrivateUse | Co: Other, Private Use |
| | NotAssigned | Cn: Other, Not Assigned |
Unicode General Categories (column 2 of the UnicodeData table) in the order they are listed in the Unicode standard.
instance Bounded GeneralCategory |
instance Enum GeneralCategory |
instance Eq GeneralCategory |
instance Ord GeneralCategory |
instance Read GeneralCategory |
instance Show GeneralCategory |
instance Ix GeneralCategory |
generalCategory :: Char -> GeneralCategory |
toUpper :: Char -> Char |
toLower :: Char -> Char |
toTitle :: Char -> Char |
digitToInt :: Char -> Int |
intToDigit :: Int -> Char |
ord :: Char -> Int |
chr :: Int -> Char |
showLitChar :: Char -> ShowS |
lexLitChar :: ReadS String |
readLitChar :: ReadS Char |