text-icu-0.8.0.2: Bindings to the ICU library
Copyright(c) 2010 Bryan O'Sullivan
LicenseBSD-style
Maintainerbos@serpentine.com
Stabilityexperimental
PortabilityGHC
Safe HaskellNone
LanguageHaskell98

Data.Text.ICU.Char

Description

Access to the Unicode Character Database, implemented as bindings to the International Components for Unicode (ICU) libraries.

Unicode assigns each codepoint (not just assigned character) values for many properties. Most are simple boolean flags, or constants from a small enumerated list. For some, values are relatively more complex types.

For more information see "About the Unicode Character Database" http://www.unicode.org/ucd/ and the ICU User Guide chapter on Properties http://icu-project.org/userguide/properties.html.

Synopsis

Working with character properties

The property function provides the main view onto the Unicode Character Database. Because Unicode character properties have a variety of types, the property function is polymorphic. The type of its first argument dictates the type of its result, by use of the Property typeclass.

For instance, property Alphabetic returns a Bool, while property NFCQuickCheck returns a Maybe Bool.

class Property p v | p -> v Source #

Minimal complete definition

fromNative, toUProperty

Instances

Instances details
Property BidiClass_ Direction Source # 
Instance details

Defined in Data.Text.ICU.Char

Property Block_ BlockCode Source # 
Instance details

Defined in Data.Text.ICU.Char

Methods

fromNative :: Block_ -> Int32 -> BlockCode

toUProperty :: Block_ -> UProperty

Property Bool_ Bool Source # 
Instance details

Defined in Data.Text.ICU.Char

Methods

fromNative :: Bool_ -> Int32 -> Bool

toUProperty :: Bool_ -> UProperty

Property CanonicalCombiningClass_ Int Source # 
Instance details

Defined in Data.Text.ICU.Char

Property EastAsianWidth_ EastAsianWidth Source # 
Instance details

Defined in Data.Text.ICU.Char

Property GeneralCategory_ GeneralCategory Source # 
Instance details

Defined in Data.Text.ICU.Char

Property LeadCanonicalCombiningClass_ Int Source # 
Instance details

Defined in Data.Text.ICU.Char

Property TrailingCanonicalCombiningClass_ Int Source # 
Instance details

Defined in Data.Text.ICU.Char

Property BidiPairedBracketType_ (Maybe BidiPairedBracketType) Source # 
Instance details

Defined in Data.Text.ICU.Char

Property Decomposition_ (Maybe Decomposition) Source # 
Instance details

Defined in Data.Text.ICU.Char

Property GraphemeClusterBreak_ (Maybe GraphemeClusterBreak) Source # 
Instance details

Defined in Data.Text.ICU.Char

Property HangulSyllableType_ (Maybe HangulSyllableType) Source # 
Instance details

Defined in Data.Text.ICU.Char

Property JoiningGroup_ (Maybe JoiningGroup) Source # 
Instance details

Defined in Data.Text.ICU.Char

Property JoiningType_ (Maybe JoiningType) Source # 
Instance details

Defined in Data.Text.ICU.Char

Property LineBreak_ (Maybe LineBreak) Source # 
Instance details

Defined in Data.Text.ICU.Char

Property NFCQuickCheck_ (Maybe Bool) Source # 
Instance details

Defined in Data.Text.ICU.Char

Property NFDQuickCheck_ (Maybe Bool) Source # 
Instance details

Defined in Data.Text.ICU.Char

Property NFKCQuickCheck_ (Maybe Bool) Source # 
Instance details

Defined in Data.Text.ICU.Char

Property NFKDQuickCheck_ (Maybe Bool) Source # 
Instance details

Defined in Data.Text.ICU.Char

Property NumericType_ (Maybe NumericType) Source # 
Instance details

Defined in Data.Text.ICU.Char

Property SentenceBreak_ (Maybe SentenceBreak) Source # 
Instance details

Defined in Data.Text.ICU.Char

Property WordBreak_ (Maybe WordBreak) Source # 
Instance details

Defined in Data.Text.ICU.Char

Property identifier types

data BidiClass_ Source #

Constructors

BidiClass 

Instances

Instances details
Show BidiClass_ Source # 
Instance details

Defined in Data.Text.ICU.Char

NFData BidiClass_ Source # 
Instance details

Defined in Data.Text.ICU.Char

Methods

rnf :: BidiClass_ -> () #

Property BidiClass_ Direction Source # 
Instance details

Defined in Data.Text.ICU.Char

data Block_ Source #

Constructors

Block 

Instances

Instances details
NFData Block_ Source # 
Instance details

Defined in Data.Text.ICU.Char

Methods

rnf :: Block_ -> () #

Property Block_ BlockCode Source # 
Instance details

Defined in Data.Text.ICU.Char

Methods

fromNative :: Block_ -> Int32 -> BlockCode

toUProperty :: Block_ -> UProperty

data Bool_ Source #

Constructors

Alphabetic 
ASCIIHexDigit

0-9, A-F, a-f

BidiControl

Format controls which have specific functions in the Bidi Algorithm.

BidiMirrored

Characters that may change display in RTL text.

Dash

Variations of dashes.

DefaultIgnorable

Ignorable in most processing.

Deprecated

The usage of deprecated characters is strongly discouraged.

Diacritic

Characters that linguistically modify the meaning of another character to which they apply.

Extender

Extend the value or shape of a preceding alphabetic character, e.g. length and iteration marks.

FullCompositionExclusion 
GraphemeBase

For programmatic determination of grapheme cluster boundaries.

GraphemeExtend

For programmatic determination of grapheme cluster boundaries.

GraphemeLink

For programmatic determination of grapheme cluster boundaries.

HexDigit

Characters commonly used for hexadecimal numbers.

Hyphen

Dashes used to mark connections between pieces of words, plus the Katakana middle dot.

IDContinue

Characters that can continue an identifier.

IDStart

Characters that can start an identifier.

Ideographic

CJKV ideographs.

IDSBinaryOperator

For programmatic determination of Ideographic Description Sequences.

IDSTrinaryOperator 
JoinControl

Format controls for cursive joining and ligation.

LogicalOrderException

Characters that do not use logical order and require special handling in most processing.

Lowercase 
Math 
NonCharacter

Code points that are explicitly defined as illegal for the encoding of characters.

QuotationMark 
Radical

For programmatic determination of Ideographic Description Sequences.

SoftDotted

Characters with a "soft dot", like i or j. An accent placed on these characters causes the dot to disappear.

TerminalPunctuation

Punctuation characters that generally mark the end of textual units.

UnifiedIdeograph

For programmatic determination of Ideographic Description Sequences.

Uppercase 
WhiteSpace 
XidContinue

IDContinue modified to allow closure under normalization forms NFKC and NFKD.

XidStart

IDStart modified to allow closure under normalization forms NFKC and NFKD.

CaseSensitive

Either the source of a case mapping or in the target of a case mapping. Not the same as the general category Cased_Letter.

STerm

Sentence Terminal. Used in UAX #29: Text Boundaries http://www.unicode.org/reports/tr29/.

VariationSelector

Indicates all those characters that qualify as Variation Selectors. For details on the behavior of these characters, see http://unicode.org/Public/UNIDATA/StandardizedVariants.html and 15.6 Variation Selectors.

NFDInert

ICU-specific property for characters that are inert under NFD, i.e. they do not interact with adjacent characters. Used for example in normalizing transforms in incremental mode to find the boundary of safely normalizable text despite possible text additions.

NFKDInert

ICU-specific property for characters that are inert under NFKD, i.e. they do not interact with adjacent characters.

NFCInert

ICU-specific property for characters that are inert under NFC, i.e. they do not interact with adjacent characters.

NFKCInert

ICU-specific property for characters that are inert under NFKC, i.e. they do not interact with adjacent characters.

SegmentStarter

ICU-specific property for characters that are starters in terms of Unicode normalization and combining character sequences.

PatternSyntax

See UAX #31 Identifier and Pattern Syntax http://www.unicode.org/reports/tr31/.

PatternWhiteSpace

See UAX #31 Identifier and Pattern Syntax http://www.unicode.org/reports/tr31/.

POSIXAlNum

Alphanumeric character class.

POSIXBlank

Blank character class.

POSIXGraph

Graph character class.

POSIXPrint

Printable character class.

POSIXXDigit

Hex digit character class.

Cased

Cased character class. For lowercase, uppercase and titlecase characters.

CaseIgnorable

Used in context-sensitive case mappings.

ChangesWhenLowercased 
ChangesWhenUppercased 
ChangesWhenTitlecased 
ChangesWhenCasefolded 
ChangesWhenCasemapped 
ChangesWhenNFKCCasefolded 
Emoji

See http://www.unicode.org/reports/tr51/#Emoji_Properties

EmojiPresentation

See http://www.unicode.org/reports/tr51/#Emoji_Properties

EmojiModifier

See http://www.unicode.org/reports/tr51/#Emoji_Properties

EmojiModifierBase

See http://www.unicode.org/reports/tr51/#Emoji_Properties

EmojiComponent

See http://www.unicode.org/reports/tr51/#Emoji_Properties

RegionalIndicator 
PrependedConcatenationMark 
ExtendedPictographic 

Instances

Instances details
Enum Bool_ Source # 
Instance details

Defined in Data.Text.ICU.Char

Show Bool_ Source # 
Instance details

Defined in Data.Text.ICU.Char

Methods

showsPrec :: Int -> Bool_ -> ShowS #

show :: Bool_ -> String #

showList :: [Bool_] -> ShowS #

NFData Bool_ Source # 
Instance details

Defined in Data.Text.ICU.Char

Methods

rnf :: Bool_ -> () #

Eq Bool_ Source # 
Instance details

Defined in Data.Text.ICU.Char

Methods

(==) :: Bool_ -> Bool_ -> Bool #

(/=) :: Bool_ -> Bool_ -> Bool #

Property Bool_ Bool Source # 
Instance details

Defined in Data.Text.ICU.Char

Methods

fromNative :: Bool_ -> Int32 -> Bool

toUProperty :: Bool_ -> UProperty

data Decomposition_ Source #

Constructors

Decomposition 

Instances

Instances details
Show Decomposition_ Source # 
Instance details

Defined in Data.Text.ICU.Char

NFData Decomposition_ Source # 
Instance details

Defined in Data.Text.ICU.Char

Methods

rnf :: Decomposition_ -> () #

Property Decomposition_ (Maybe Decomposition) Source # 
Instance details

Defined in Data.Text.ICU.Char

data EastAsianWidth_ Source #

Constructors

EastAsianWidth 

Instances

Instances details
Show EastAsianWidth_ Source # 
Instance details

Defined in Data.Text.ICU.Char

NFData EastAsianWidth_ Source # 
Instance details

Defined in Data.Text.ICU.Char

Methods

rnf :: EastAsianWidth_ -> () #

Property EastAsianWidth_ EastAsianWidth Source # 
Instance details

Defined in Data.Text.ICU.Char

data JoiningGroup_ Source #

Constructors

JoiningGroup 

Instances

Instances details
Show JoiningGroup_ Source # 
Instance details

Defined in Data.Text.ICU.Char

NFData JoiningGroup_ Source # 
Instance details

Defined in Data.Text.ICU.Char

Methods

rnf :: JoiningGroup_ -> () #

Property JoiningGroup_ (Maybe JoiningGroup) Source # 
Instance details

Defined in Data.Text.ICU.Char

data JoiningType_ Source #

Constructors

JoiningType 

Instances

Instances details
Show JoiningType_ Source # 
Instance details

Defined in Data.Text.ICU.Char

NFData JoiningType_ Source # 
Instance details

Defined in Data.Text.ICU.Char

Methods

rnf :: JoiningType_ -> () #

Property JoiningType_ (Maybe JoiningType) Source # 
Instance details

Defined in Data.Text.ICU.Char

data NumericType_ Source #

Constructors

NumericType 

Instances

Instances details
Show NumericType_ Source # 
Instance details

Defined in Data.Text.ICU.Char

NFData NumericType_ Source # 
Instance details

Defined in Data.Text.ICU.Char

Methods

rnf :: NumericType_ -> () #

Property NumericType_ (Maybe NumericType) Source # 
Instance details

Defined in Data.Text.ICU.Char

Combining class

Normalization checking

data NFCQuickCheck_ Source #

Constructors

NFCQuickCheck 

Instances

Instances details
Show NFCQuickCheck_ Source # 
Instance details

Defined in Data.Text.ICU.Char

NFData NFCQuickCheck_ Source # 
Instance details

Defined in Data.Text.ICU.Char

Methods

rnf :: NFCQuickCheck_ -> () #

Property NFCQuickCheck_ (Maybe Bool) Source # 
Instance details

Defined in Data.Text.ICU.Char

data NFDQuickCheck_ Source #

Constructors

NFDQuickCheck 

Instances

Instances details
Show NFDQuickCheck_ Source # 
Instance details

Defined in Data.Text.ICU.Char

NFData NFDQuickCheck_ Source # 
Instance details

Defined in Data.Text.ICU.Char

Methods

rnf :: NFDQuickCheck_ -> () #

Property NFDQuickCheck_ (Maybe Bool) Source # 
Instance details

Defined in Data.Text.ICU.Char

data NFKCQuickCheck_ Source #

Constructors

NFKCQuickCheck 

Instances

Instances details
Show NFKCQuickCheck_ Source # 
Instance details

Defined in Data.Text.ICU.Char

NFData NFKCQuickCheck_ Source # 
Instance details

Defined in Data.Text.ICU.Char

Methods

rnf :: NFKCQuickCheck_ -> () #

Property NFKCQuickCheck_ (Maybe Bool) Source # 
Instance details

Defined in Data.Text.ICU.Char

data NFKDQuickCheck_ Source #

Constructors

NFKDQuickCheck 

Instances

Instances details
Show NFKDQuickCheck_ Source # 
Instance details

Defined in Data.Text.ICU.Char

NFData NFKDQuickCheck_ Source # 
Instance details

Defined in Data.Text.ICU.Char

Methods

rnf :: NFKDQuickCheck_ -> () #

Property NFKDQuickCheck_ (Maybe Bool) Source # 
Instance details

Defined in Data.Text.ICU.Char

Text boundaries

data LineBreak_ Source #

Constructors

LineBreak 

Instances

Instances details
Show LineBreak_ Source # 
Instance details

Defined in Data.Text.ICU.Char

NFData LineBreak_ Source # 
Instance details

Defined in Data.Text.ICU.Char

Methods

rnf :: LineBreak_ -> () #

Property LineBreak_ (Maybe LineBreak) Source # 
Instance details

Defined in Data.Text.ICU.Char

data SentenceBreak_ Source #

Constructors

SentenceBreak 

Instances

Instances details
Show SentenceBreak_ Source # 
Instance details

Defined in Data.Text.ICU.Char

NFData SentenceBreak_ Source # 
Instance details

Defined in Data.Text.ICU.Char

Methods

rnf :: SentenceBreak_ -> () #

Property SentenceBreak_ (Maybe SentenceBreak) Source # 
Instance details

Defined in Data.Text.ICU.Char

data WordBreak_ Source #

Constructors

WordBreak 

Instances

Instances details
Show WordBreak_ Source # 
Instance details

Defined in Data.Text.ICU.Char

NFData WordBreak_ Source # 
Instance details

Defined in Data.Text.ICU.Char

Methods

rnf :: WordBreak_ -> () #

Property WordBreak_ (Maybe WordBreak) Source # 
Instance details

Defined in Data.Text.ICU.Char

Property value types

data BlockCode Source #

Descriptions of Unicode blocks.

Constructors

NoBlock 
BasicLatin 
Latin1Supplement 
LatinExtendedA 
LatinExtendedB 
IPAExtensions 
SpacingModifierLetters 
CombiningDiacriticalMarks 
GreekAndCoptic 
Cyrillic 
Armenian 
Hebrew 
Arabic 
Syriac 
Thaana 
Devanagari 
Bengali 
Gurmukhi 
Gujarati 
Oriya 
Tamil 
Telugu 
Kannada 
Malayalam 
Sinhala 
Thai 
Lao 
Tibetan 
Myanmar 
Georgian 
HangulJamo 
Ethiopic 
Cherokee 
UnifiedCanadianAboriginalSyllabics 
Ogham 
Runic 
Khmer 
Mongolian 
LatinExtendedAdditional 
GreekExtended 
GeneralPunctuation 
SuperscriptsAndSubscripts 
CurrencySymbols 
CombiningDiacriticalMarksForSymbols 
LetterlikeSymbols 
NumberForms 
Arrows 
MathematicalOperators 
MiscellaneousTechnical 
ControlPictures 
OpticalCharacterRecognition 
EnclosedAlphanumerics 
BoxDrawing 
BlockElements 
GeometricShapes 
MiscellaneousSymbols 
Dingbats 
BraillePatterns 
CJKRadicalsSupplement 
KangxiRadicals 
IdeographicDescriptionCharacters 
CJKSymbolsAndPunctuation 
Hiragana 
Katakana 
Bopomofo 
HangulCompatibilityJamo 
Kanbun 
BopomofoExtended 
EnclosedCJKLettersAndMonths 
CJKCompatibility 
CJKUnifiedIdeographsExtensionA 
CJKUnifiedIdeographs 
YiSyllables 
YiRadicals 
HangulSyllables 
HighSurrogates 
HighPrivateUseSurrogates 
LowSurrogates 
PrivateUseArea 
CJKCompatibilityIdeographs 
AlphabeticPresentationForms 
ArabicPresentationFormsA 
CombiningHalfMarks 
CJKCompatibilityForms 
SmallFormVariants 
ArabicPresentationFormsB 
Specials 
HalfwidthAndFullwidthForms 
OldItalic 
Gothic 
Deseret 
ByzantineMusicalSymbols 
MusicalSymbols 
MathematicalAlphanumericSymbols 
CJKUnifiedIdeographsExtensionB 
CJKCompatibilityIdeographsSupplement 
Tags 
CyrillicSupplement 
Tagalog 
Hanunoo 
Buhid 
Tagbanwa 
MiscellaneousMathematicalSymbolsA 
SupplementalArrowsA 
SupplementalArrowsB 
MiscellaneousMathematicalSymbolsB 
SupplementalMathematicalOperators 
KatakanaPhoneticExtensions 
VariationSelectors 
SupplementaryPrivateUseAreaA 
SupplementaryPrivateUseAreaB 
Limbu 
TaiLe 
KhmerSymbols 
PhoneticExtensions 
MiscellaneousSymbolsAndArrows 
YijingHexagramSymbols 
LinearBSyllabary 
LinearBIdeograms 
AegeanNumbers 
Ugaritic 
Shavian 
Osmanya 
CypriotSyllabary 
TaiXuanJingSymbols 
VariationSelectorsSupplement 
AncientGreekMusicalNotation 
AncientGreekNumbers 
ArabicSupplement 
Buginese 
CJKStrokes 
CombiningDiacriticalMarksSupplement 
Coptic 
EthiopicExtended 
EthiopicSupplement 
GeorgianSupplement 
Glagolitic 
Kharoshthi 
ModifierToneLetters 
NewTaiLue 
OldPersian 
PhoneticExtensionsSupplement 
SupplementalPunctuation 
SylotiNagri 
Tifinagh 
VerticalForms 
N'Ko 
Balinese 
LatinExtendedC 
LatinExtendedD 
PhagsPa 
Phoenician 
Cuneiform 
CuneiformNumbersAndPunctuation 
CountingRodNumerals 
Sundanese 
Lepcha 
OlChiki 
CyrillicExtendedA 
Vai 
CyrillicExtendedB 
Saurashtra 
KayahLi 
Rejang 
Cham 
AncientSymbols 
PhaistosDisc 
Lycian 
Carian 
Lydian 
MahjongTiles 
DominoTiles 
Samaritan 
UnifiedCanadianAboriginalSyllabicsExtended 
TaiTham 
VedicExtensions 
Lisu 
Bamum 
CommonIndicNumberForms 
DevanagariExtended 
HangulJamoExtendedA 
Javanese 
MyanmarExtendedA 
TaiViet 
MeeteiMayek 
HangulJamoExtendedB 
ImperialAramaic 
OldSouthArabian 
Avestan 
InscriptionalParthian 
InscriptionalPahlavi 
OldTurkic 
RumiNumeralSymbols 
Kaithi 
EgyptianHieroglyphs 
EnclosedAlphanumericSupplement 
EnclosedIdeographicSupplement 
CJKUnifiedIdeographsExtensionC 
Mandaic 
Batak 
EthiopicExtendedA 
Brahmi 
BamumSupplement 
KanaSupplement 
PlayingCards 
MiscellaneousSymbolsAndPictographs 
Emoticons 
TransportAndMapSymbols 
AlchemicalSymbols 
CJKUnifiedIdeographsExtensionD 
ArabicExtendedA 
ArabicMathematicalAlphabeticSymbols 
Chakma 
MeeteiMayekExtensions 
MeroiticCursive 
MeroiticHieroglyphs 
Miao 
Sharada 
SoraSompeng 
SundaneseSupplement 
Takri 
BassaVah 
CaucasianAlbanian 
CopticEpactNumbers 
CombiningDiacriticalMarksExtended 
Duployan 
Elbasan 
GeometricShapesExtended 
Grantha 
Khojki 
Khudawadi 
LatinExtendedE 
LinearA 
Mahajani 
Manichaean 
MendeKikakui 
Modi 
Mro 
MyanmarExtendedB 
Nabataean 
OldNorthArabian 
OldPermic 
OrnamentalDingbats 
PahawhHmong 
Palmyrene 
PauCinHau 
PsalterPahlavi 
ShorthandFormatControls 
Siddham 
SinhalaArchaicNumbers 
SupplementalArrowsC 
Tirhuta 
WarangCiti 
Ahom 
AnatolianHieroglyphs 
CherokeeSupplement 
CJKUnifiedIdeographsExtensionE 
EarlyDynasticCuneiform 
Hatran 
Multani 
OldHungarian 
SupplementalSymbolsAndPictographs 
SuttonSignwriting 
Adlam 
Bhaiksuki 
CyrillicExtendedC 
GlagoliticSupplement 
IdeographicSymbolsAndPunctuation 
Marchen 
MongolianSupplement 
Newa 
Osage 
Tangut 
TangutComponents 
CjkUnifiedIdeographsExtensionF 
KanaExtendedA 
MasaramGondi 
Nushu 
Soyombo 
SyriacSupplement 
ZanabazarSquare 
ChessSymbols 
Dogra 
GeorgianExtended 
GunjalaGondi 
HanifiRohingya 
IndicSiyaqNumbers 
Makasar 
MayanNumerals 
Medefaidrin 
OldSogdian 
Sogdian 
EgyptianHieroglyphFormatControls 
Elymaic 
Nandinagari 
NyiakengPuachueHmong 
OttomanSiyaqNumbers 
SmallKanaExtension 
SymbolsAndPictographsExtendedA 
TamilSupplement 
Wancho 
Chorasmian 
CjkUnifiedIdeographsExtensionG 
DivesAkuru 
KhitanSmallScript 
LisuSupplement 
SymbolsForLegacyComputing 
TangutSupplement 
Yezidi 
ArabicExtendedB 
CyproMinoan 
EthiopicExtendedB 
KanaExtendedB 
LatinExtendedF 
LatinExtendedG 
OldUyghur 
Tangsa 
Toto 
UnifiedCanadianAboriginalSyllabicsExtendedA 
Vithkuqi 
ZnamennyMusicalNotation 

Instances

Instances details
Bounded BlockCode Source # 
Instance details

Defined in Data.Text.ICU.Char

Enum BlockCode Source # 
Instance details

Defined in Data.Text.ICU.Char

Show BlockCode Source # 
Instance details

Defined in Data.Text.ICU.Char

NFData BlockCode Source # 
Instance details

Defined in Data.Text.ICU.Char

Methods

rnf :: BlockCode -> () #

Eq BlockCode Source # 
Instance details

Defined in Data.Text.ICU.Char

Property Block_ BlockCode Source # 
Instance details

Defined in Data.Text.ICU.Char

Methods

fromNative :: Block_ -> Int32 -> BlockCode

toUProperty :: Block_ -> UProperty

data Direction Source #

The language directional property of a character set.

Instances

Instances details
Enum Direction Source # 
Instance details

Defined in Data.Text.ICU.Char

Show Direction Source # 
Instance details

Defined in Data.Text.ICU.Char

NFData Direction Source # 
Instance details

Defined in Data.Text.ICU.Char

Methods

rnf :: Direction -> () #

Eq Direction Source # 
Instance details

Defined in Data.Text.ICU.Char

Property BidiClass_ Direction Source # 
Instance details

Defined in Data.Text.ICU.Char

data GeneralCategory Source #

data HangulSyllableType Source #

data JoiningGroup Source #

Text boundaries

data GraphemeClusterBreak Source #

data LineBreak Source #

data BidiPairedBracketType Source #

Constructors

BPTNone 
BPTOpen 
BPTClose 

Functions

blockCode :: Char -> BlockCode Source #

Return the Unicode allocation block that contains the given character.

charFullName :: Char -> String Source #

Return the full name of a Unicode character.

Compared to charName, this function gives each Unicode codepoint a unique extended name. Extended names are lowercase followed by an uppercase hexadecimal number, within angle brackets.

charName :: Char -> String Source #

Return the name of a Unicode character.

The names of all unassigned characters are empty.

The name contains only "invariant" characters like A-Z, 0-9, space, and '-'.

charFromFullName :: String -> Maybe Char Source #

Find a Unicode character by its full or extended name, and return its codepoint value.

The name is matched exactly and completely.

A Unicode 1.0 name is matched only if it differs from the modern name.

Compared to charFromName, this function gives each Unicode code point a unique extended name. Extended names are lowercase followed by an uppercase hexadecimal number, within angle brackets.

charFromName :: String -> Maybe Char Source #

Find a Unicode character by its full name, and return its code point value.

The name is matched exactly and completely.

A Unicode 1.0 name is matched only if it differs from the modern name. Unicode names are all uppercase.

direction :: Char -> Direction Source #

Return the bidirectional category value for the codepoint, which is used in the Unicode bidirectional algorithm (UAX #9 http://www.unicode.org/reports/tr9/).

property :: Property p v => p -> Char -> v Source #

isMirrored :: Char -> Bool Source #

Determine whether the codepoint has the BidiMirrored property. This property is set for characters that are commonly used in Right-To-Left contexts and need to be displayed with a "mirrored" glyph.

Conversion to numbers

digitToInt :: Char -> Maybe Int Source #

Return the decimal digit value of a decimal digit character. Such characters have the general category Nd (decimal digit numbers) and a NumericType_ of NTDecimal.

No digit values are returned for any Han characters, because Han number characters are often used with a special Chinese-style number format (with characters for powers of 10 in between) instead of in decimal-positional notation. Unicode 4 explicitly assigns Han number characters a NumericType_ of NTNumeric instead of NTDecimal.

numericValue :: Char -> Maybe Double Source #

Return the numeric value for a Unicode codepoint as defined in the Unicode Character Database.

A Double return type is necessary because some numeric values are fractions, negative, or too large to fit in a fixed-width integral type.