Copyright | (c) 2010 Bryan O'Sullivan |
---|---|
License | BSD-style |
Maintainer | bos@serpentine.com |
Stability | experimental |
Portability | GHC |
Safe Haskell | None |
Language | Haskell98 |
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 code point (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
- class Property p v | p -> v
- data BidiClass_ = BidiClass
- data Block_ = Block
- data Bool_
- = Alphabetic
- | ASCIIHexDigit
- | BidiControl
- | BidiMirrored
- | Dash
- | DefaultIgnorable
- | Deprecated
- | Diacritic
- | Extender
- | FullCompositionExclusion
- | GraphemeBase
- | GraphemeExtend
- | GraphemeLink
- | HexDigit
- | Hyphen
- | IDContinue
- | IDStart
- | Ideographic
- | IDSBinaryOperator
- | IDSTrinaryOperator
- | JoinControl
- | LogicalOrderException
- | Lowercase
- | Math
- | NonCharacter
- | QuotationMark
- | Radical
- | SoftDotted
- | TerminalPunctuation
- | UnifiedIdeograph
- | Uppercase
- | WhiteSpace
- | XidContinue
- | XidStart
- | CaseSensitive
- | STerm
- | VariationSelector
- | NFDInert
- | NFKDInert
- | NFCInert
- | NFKCInert
- | SegmentStarter
- | PatternSyntax
- | PatternWhiteSpace
- | POSIXAlNum
- | POSIXBlank
- | POSIXGraph
- | POSIXPrint
- | POSIXXDigit
- | Cased
- | CaseIgnorable
- | ChangesWhenLowercased
- | ChangesWhenUppercased
- | ChangesWhenTitlecased
- | ChangesWhenCasefolded
- | ChangesWhenCasemapped
- | ChangesWhenNFKCCasefolded
- data Decomposition_ = Decomposition
- data EastAsianWidth_ = EastAsianWidth
- data GeneralCategory_ = GeneralCategory
- data HangulSyllableType_ = HangulSyllableType
- data JoiningGroup_ = JoiningGroup
- data JoiningType_ = JoiningType
- data NumericType_ = NumericType
- data CanonicalCombiningClass_ = CanonicalCombiningClass
- data LeadCanonicalCombiningClass_ = LeadCanonicalCombiningClass
- data TrailingCanonicalCombiningClass_ = TrailingCanonicalCombiningClass
- data NFCQuickCheck_ = NFCQuickCheck
- data NFDQuickCheck_ = NFDQuickCheck
- data NFKCQuickCheck_ = NFKCQuickCheck
- data NFKDQuickCheck_ = NFKDQuickCheck
- data GraphemeClusterBreak_ = GraphemeClusterBreak
- data LineBreak_ = LineBreak
- data SentenceBreak_ = SentenceBreak
- data WordBreak_ = WordBreak
- data BidiPairedBracketType_ = BidiPairedBracketType
- data BlockCode
- = 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
- data Direction
- = LeftToRight
- | RightToLeft
- | EuropeanNumber
- | EuropeanNumberSeparator
- | EuropeanNumberTerminator
- | ArabicNumber
- | CommonNumberSeparator
- | BlockSeparator
- | SegmentSeparator
- | WhiteSpaceNeutral
- | OtherNeutral
- | LeftToRightEmbedding
- | LeftToRightOverride
- | RightToLeftArabic
- | RightToLeftEmbedding
- | RightToLeftOverride
- | PopDirectionalFormat
- | DirNonSpacingMark
- | BoundaryNeutral
- data Decomposition
- data EastAsianWidth
- data GeneralCategory
- = GeneralOtherType
- | UppercaseLetter
- | LowercaseLetter
- | TitlecaseLetter
- | ModifierLetter
- | OtherLetter
- | NonSpacingMark
- | EnclosingMark
- | CombiningSpacingMark
- | DecimalDigitNumber
- | LetterNumber
- | OtherNumber
- | SpaceSeparator
- | LineSeparator
- | ParagraphSeparator
- | ControlChar
- | FormatChar
- | PrivateUseChar
- | Surrogate
- | DashPunctuation
- | StartPunctuation
- | EndPunctuation
- | ConnectorPunctuation
- | OtherPunctuation
- | MathSymbol
- | CurrencySymbol
- | ModifierSymbol
- | OtherSymbol
- | InitialPunctuation
- | FinalPunctuation
- data HangulSyllableType
- data JoiningGroup
- = Ain
- | Alaph
- | Alef
- | Beh
- | Beth
- | Dal
- | DalathRish
- | E
- | Feh
- | FinalSemkath
- | Gaf
- | Gamal
- | Hah
- | HamzaOnHehGoal
- | He
- | Heh
- | HehGoal
- | Heth
- | Kaf
- | Kaph
- | KnottedHeh
- | Lam
- | Lamadh
- | Meem
- | Mim
- | Noon
- | Nun
- | Pe
- | Qaf
- | Qaph
- | Reh
- | ReversedPe
- | Sad
- | Sadhe
- | Seen
- | Semkath
- | Shin
- | SwashKaf
- | SyriacWaw
- | Tah
- | Taw
- | TehMarbuta
- | Teth
- | Waw
- | Yeh
- | YehBarree
- | YehWithTail
- | Yudh
- | YudhHe
- | Zain
- | Fe
- | Khaph
- | Zhain
- | BurushaskiYehBarree
- | FarsiYeh
- | Nya
- | RohingyaYeh
- | ManichaeanAleph
- | ManichaeanAyin
- | ManichaeanBeth
- | ManichaeanDaleth
- | ManichaeanDhamedh
- | ManichaeanFive
- | ManichaeanGimel
- | ManichaeanHeth
- | ManichaeanHundred
- | ManichaeanKaph
- | ManichaeanLamedh
- | ManichaeanMem
- | ManichaeanNun
- | ManichaeanOne
- | ManichaeanPe
- | ManichaeanQoph
- | ManichaeanResh
- | ManichaeanSadhe
- | ManichaeanSamekh
- | ManichaeanTaw
- | ManichaeanTen
- | ManichaeanTeth
- | ManichaeanThamedh
- | ManichaeanTwenty
- | ManichaeanWaw
- | ManichaeanYodh
- | ManichaeanZayin
- | StraightWaw
- data JoiningType
- data NumericType
- data GraphemeClusterBreak
- data LineBreak
- = Ambiguous
- | LBAlphabetic
- | BreakBoth
- | BreakAfter
- | BreakBefore
- | MandatoryBreak
- | ContingentBreak
- | ClosePunctuation
- | CombiningMark
- | CarriageReturn
- | Exclamation
- | Glue
- | LBHyphen
- | LBIdeographic
- | Inseparable
- | InfixNumeric
- | LineFeed
- | Nonstarter
- | Numeric
- | OpenPunctuation
- | PostfixNumeric
- | PrefixNumeric
- | Quotation
- | ComplexContext
- | LBSurrogate
- | Space
- | BreakSymbols
- | Zwspace
- | NextLine
- | WordJoiner
- | H2
- | H3
- | JL
- | JT
- | JV
- | CloseParenthesis
- | ConditionalJapaneseStarter
- | LBHebrewLetter
- | LBRegionalIndicator
- data SentenceBreak
- data WordBreak
- data BidiPairedBracketType
- blockCode :: Char -> BlockCode
- charFullName :: Char -> String
- charName :: Char -> String
- charFromFullName :: String -> Maybe Char
- charFromName :: String -> Maybe Char
- combiningClass :: Char -> Int
- direction :: Char -> Direction
- property :: Property p v => p -> Char -> v
- isMirrored :: Char -> Bool
- mirror :: Char -> Char
- digitToInt :: Char -> Maybe Int
- numericValue :: Char -> Maybe Double
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,
returns a property
Alphabetic
Bool
, while
returns a property
NFCQuickCheck
.Maybe
Bool
class Property p v | p -> v Source #
Minimal complete definition
fromNative, toUProperty
Instances
Property identifier types
data BidiClass_ Source #
Constructors
BidiClass |
Instances
Show BidiClass_ Source # | |
Defined in Data.Text.ICU.Char Methods showsPrec :: Int -> BidiClass_ -> ShowS # show :: BidiClass_ -> String # showList :: [BidiClass_] -> ShowS # | |
NFData BidiClass_ Source # | |
Defined in Data.Text.ICU.Char Methods rnf :: BidiClass_ -> () # | |
Property BidiClass_ Direction Source # | |
Defined in Data.Text.ICU.Char |
Constructors
Block |
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 |
|
XidStart |
|
CaseSensitive | Either the source of a case mapping or in the target of a case
mapping. Not the same as the general category |
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 |
data Decomposition_ Source #
Constructors
Decomposition |
Instances
Show Decomposition_ Source # | |
Defined in Data.Text.ICU.Char Methods showsPrec :: Int -> Decomposition_ -> ShowS # show :: Decomposition_ -> String # showList :: [Decomposition_] -> ShowS # | |
NFData Decomposition_ Source # | |
Defined in Data.Text.ICU.Char Methods rnf :: Decomposition_ -> () # | |
Property Decomposition_ (Maybe Decomposition) Source # | |
Defined in Data.Text.ICU.Char Methods fromNative :: Decomposition_ -> Int32 -> Maybe Decomposition toUProperty :: Decomposition_ -> UProperty |
data EastAsianWidth_ Source #
Constructors
EastAsianWidth |
Instances
Show EastAsianWidth_ Source # | |
Defined in Data.Text.ICU.Char Methods showsPrec :: Int -> EastAsianWidth_ -> ShowS # show :: EastAsianWidth_ -> String # showList :: [EastAsianWidth_] -> ShowS # | |
NFData EastAsianWidth_ Source # | |
Defined in Data.Text.ICU.Char Methods rnf :: EastAsianWidth_ -> () # | |
Property EastAsianWidth_ EastAsianWidth Source # | |
Defined in Data.Text.ICU.Char Methods fromNative :: EastAsianWidth_ -> Int32 -> EastAsianWidth toUProperty :: EastAsianWidth_ -> UProperty |
data GeneralCategory_ Source #
Constructors
GeneralCategory |
Instances
Show GeneralCategory_ Source # | |
Defined in Data.Text.ICU.Char Methods showsPrec :: Int -> GeneralCategory_ -> ShowS # show :: GeneralCategory_ -> String # showList :: [GeneralCategory_] -> ShowS # | |
NFData GeneralCategory_ Source # | |
Defined in Data.Text.ICU.Char Methods rnf :: GeneralCategory_ -> () # | |
Property GeneralCategory_ GeneralCategory Source # | |
Defined in Data.Text.ICU.Char Methods fromNative :: GeneralCategory_ -> Int32 -> GeneralCategory toUProperty :: GeneralCategory_ -> UProperty |
data HangulSyllableType_ Source #
Constructors
HangulSyllableType |
Instances
Show HangulSyllableType_ Source # | |
Defined in Data.Text.ICU.Char Methods showsPrec :: Int -> HangulSyllableType_ -> ShowS # show :: HangulSyllableType_ -> String # showList :: [HangulSyllableType_] -> ShowS # | |
NFData HangulSyllableType_ Source # | |
Defined in Data.Text.ICU.Char Methods rnf :: HangulSyllableType_ -> () # | |
Property HangulSyllableType_ (Maybe HangulSyllableType) Source # | |
Defined in Data.Text.ICU.Char Methods fromNative :: HangulSyllableType_ -> Int32 -> Maybe HangulSyllableType toUProperty :: HangulSyllableType_ -> UProperty |
data JoiningGroup_ Source #
Constructors
JoiningGroup |
Instances
Show JoiningGroup_ Source # | |
Defined in Data.Text.ICU.Char Methods showsPrec :: Int -> JoiningGroup_ -> ShowS # show :: JoiningGroup_ -> String # showList :: [JoiningGroup_] -> ShowS # | |
NFData JoiningGroup_ Source # | |
Defined in Data.Text.ICU.Char Methods rnf :: JoiningGroup_ -> () # | |
Property JoiningGroup_ (Maybe JoiningGroup) Source # | |
Defined in Data.Text.ICU.Char Methods fromNative :: JoiningGroup_ -> Int32 -> Maybe JoiningGroup toUProperty :: JoiningGroup_ -> UProperty |
data JoiningType_ Source #
Constructors
JoiningType |
Instances
Show JoiningType_ Source # | |
Defined in Data.Text.ICU.Char Methods showsPrec :: Int -> JoiningType_ -> ShowS # show :: JoiningType_ -> String # showList :: [JoiningType_] -> ShowS # | |
NFData JoiningType_ Source # | |
Defined in Data.Text.ICU.Char Methods rnf :: JoiningType_ -> () # | |
Property JoiningType_ (Maybe JoiningType) Source # | |
Defined in Data.Text.ICU.Char Methods fromNative :: JoiningType_ -> Int32 -> Maybe JoiningType toUProperty :: JoiningType_ -> UProperty |
data NumericType_ Source #
Constructors
NumericType |
Instances
Show NumericType_ Source # | |
Defined in Data.Text.ICU.Char Methods showsPrec :: Int -> NumericType_ -> ShowS # show :: NumericType_ -> String # showList :: [NumericType_] -> ShowS # | |
NFData NumericType_ Source # | |
Defined in Data.Text.ICU.Char Methods rnf :: NumericType_ -> () # | |
Property NumericType_ (Maybe NumericType) Source # | |
Defined in Data.Text.ICU.Char Methods fromNative :: NumericType_ -> Int32 -> Maybe NumericType toUProperty :: NumericType_ -> UProperty |
Combining class
data CanonicalCombiningClass_ Source #
Constructors
CanonicalCombiningClass |
Instances
Show CanonicalCombiningClass_ Source # | |
Defined in Data.Text.ICU.Char Methods showsPrec :: Int -> CanonicalCombiningClass_ -> ShowS # show :: CanonicalCombiningClass_ -> String # showList :: [CanonicalCombiningClass_] -> ShowS # | |
NFData CanonicalCombiningClass_ Source # | |
Defined in Data.Text.ICU.Char Methods rnf :: CanonicalCombiningClass_ -> () # | |
Property CanonicalCombiningClass_ Int Source # | |
Defined in Data.Text.ICU.Char Methods fromNative :: CanonicalCombiningClass_ -> Int32 -> Int toUProperty :: CanonicalCombiningClass_ -> UProperty |
data LeadCanonicalCombiningClass_ Source #
Constructors
LeadCanonicalCombiningClass |
Instances
Show LeadCanonicalCombiningClass_ Source # | |
Defined in Data.Text.ICU.Char Methods showsPrec :: Int -> LeadCanonicalCombiningClass_ -> ShowS # show :: LeadCanonicalCombiningClass_ -> String # showList :: [LeadCanonicalCombiningClass_] -> ShowS # | |
NFData LeadCanonicalCombiningClass_ Source # | |
Defined in Data.Text.ICU.Char Methods rnf :: LeadCanonicalCombiningClass_ -> () # | |
Property LeadCanonicalCombiningClass_ Int Source # | |
Defined in Data.Text.ICU.Char Methods fromNative :: LeadCanonicalCombiningClass_ -> Int32 -> Int toUProperty :: LeadCanonicalCombiningClass_ -> UProperty |
data TrailingCanonicalCombiningClass_ Source #
Constructors
TrailingCanonicalCombiningClass |
Instances
Show TrailingCanonicalCombiningClass_ Source # | |
Defined in Data.Text.ICU.Char Methods showsPrec :: Int -> TrailingCanonicalCombiningClass_ -> ShowS # | |
NFData TrailingCanonicalCombiningClass_ Source # | |
Defined in Data.Text.ICU.Char Methods rnf :: TrailingCanonicalCombiningClass_ -> () # | |
Property TrailingCanonicalCombiningClass_ Int Source # | |
Defined in Data.Text.ICU.Char Methods fromNative :: TrailingCanonicalCombiningClass_ -> Int32 -> Int toUProperty :: TrailingCanonicalCombiningClass_ -> UProperty |
Normalization checking
data NFCQuickCheck_ Source #
Constructors
NFCQuickCheck |
Instances
Show NFCQuickCheck_ Source # | |
Defined in Data.Text.ICU.Char Methods showsPrec :: Int -> NFCQuickCheck_ -> ShowS # show :: NFCQuickCheck_ -> String # showList :: [NFCQuickCheck_] -> ShowS # | |
NFData NFCQuickCheck_ Source # | |
Defined in Data.Text.ICU.Char Methods rnf :: NFCQuickCheck_ -> () # | |
Property NFCQuickCheck_ (Maybe Bool) Source # | |
Defined in Data.Text.ICU.Char Methods fromNative :: NFCQuickCheck_ -> Int32 -> Maybe Bool toUProperty :: NFCQuickCheck_ -> UProperty |
data NFDQuickCheck_ Source #
Constructors
NFDQuickCheck |
Instances
Show NFDQuickCheck_ Source # | |
Defined in Data.Text.ICU.Char Methods showsPrec :: Int -> NFDQuickCheck_ -> ShowS # show :: NFDQuickCheck_ -> String # showList :: [NFDQuickCheck_] -> ShowS # | |
NFData NFDQuickCheck_ Source # | |
Defined in Data.Text.ICU.Char Methods rnf :: NFDQuickCheck_ -> () # | |
Property NFDQuickCheck_ (Maybe Bool) Source # | |
Defined in Data.Text.ICU.Char Methods fromNative :: NFDQuickCheck_ -> Int32 -> Maybe Bool toUProperty :: NFDQuickCheck_ -> UProperty |
data NFKCQuickCheck_ Source #
Constructors
NFKCQuickCheck |
Instances
Show NFKCQuickCheck_ Source # | |
Defined in Data.Text.ICU.Char Methods showsPrec :: Int -> NFKCQuickCheck_ -> ShowS # show :: NFKCQuickCheck_ -> String # showList :: [NFKCQuickCheck_] -> ShowS # | |
NFData NFKCQuickCheck_ Source # | |
Defined in Data.Text.ICU.Char Methods rnf :: NFKCQuickCheck_ -> () # | |
Property NFKCQuickCheck_ (Maybe Bool) Source # | |
Defined in Data.Text.ICU.Char Methods fromNative :: NFKCQuickCheck_ -> Int32 -> Maybe Bool toUProperty :: NFKCQuickCheck_ -> UProperty |
data NFKDQuickCheck_ Source #
Constructors
NFKDQuickCheck |
Instances
Show NFKDQuickCheck_ Source # | |
Defined in Data.Text.ICU.Char Methods showsPrec :: Int -> NFKDQuickCheck_ -> ShowS # show :: NFKDQuickCheck_ -> String # showList :: [NFKDQuickCheck_] -> ShowS # | |
NFData NFKDQuickCheck_ Source # | |
Defined in Data.Text.ICU.Char Methods rnf :: NFKDQuickCheck_ -> () # | |
Property NFKDQuickCheck_ (Maybe Bool) Source # | |
Defined in Data.Text.ICU.Char Methods fromNative :: NFKDQuickCheck_ -> Int32 -> Maybe Bool toUProperty :: NFKDQuickCheck_ -> UProperty |
Text boundaries
data GraphemeClusterBreak_ Source #
Constructors
GraphemeClusterBreak |
Instances
Show GraphemeClusterBreak_ Source # | |
Defined in Data.Text.ICU.Char Methods showsPrec :: Int -> GraphemeClusterBreak_ -> ShowS # show :: GraphemeClusterBreak_ -> String # showList :: [GraphemeClusterBreak_] -> ShowS # | |
NFData GraphemeClusterBreak_ Source # | |
Defined in Data.Text.ICU.Char Methods rnf :: GraphemeClusterBreak_ -> () # | |
Property GraphemeClusterBreak_ (Maybe GraphemeClusterBreak) Source # | |
Defined in Data.Text.ICU.Char Methods fromNative :: GraphemeClusterBreak_ -> Int32 -> Maybe GraphemeClusterBreak toUProperty :: GraphemeClusterBreak_ -> UProperty |
data LineBreak_ Source #
Constructors
LineBreak |
Instances
Show LineBreak_ Source # | |
Defined in Data.Text.ICU.Char Methods showsPrec :: Int -> LineBreak_ -> ShowS # show :: LineBreak_ -> String # showList :: [LineBreak_] -> ShowS # | |
NFData LineBreak_ Source # | |
Defined in Data.Text.ICU.Char Methods rnf :: LineBreak_ -> () # | |
Property LineBreak_ (Maybe LineBreak) Source # | |
Defined in Data.Text.ICU.Char |
data SentenceBreak_ Source #
Constructors
SentenceBreak |
Instances
Show SentenceBreak_ Source # | |
Defined in Data.Text.ICU.Char Methods showsPrec :: Int -> SentenceBreak_ -> ShowS # show :: SentenceBreak_ -> String # showList :: [SentenceBreak_] -> ShowS # | |
NFData SentenceBreak_ Source # | |
Defined in Data.Text.ICU.Char Methods rnf :: SentenceBreak_ -> () # | |
Property SentenceBreak_ (Maybe SentenceBreak) Source # | |
Defined in Data.Text.ICU.Char Methods fromNative :: SentenceBreak_ -> Int32 -> Maybe SentenceBreak toUProperty :: SentenceBreak_ -> UProperty |
data WordBreak_ Source #
Constructors
WordBreak |
Instances
Show WordBreak_ Source # | |
Defined in Data.Text.ICU.Char Methods showsPrec :: Int -> WordBreak_ -> ShowS # show :: WordBreak_ -> String # showList :: [WordBreak_] -> ShowS # | |
NFData WordBreak_ Source # | |
Defined in Data.Text.ICU.Char Methods rnf :: WordBreak_ -> () # | |
Property WordBreak_ (Maybe WordBreak) Source # | |
Defined in Data.Text.ICU.Char |
data BidiPairedBracketType_ Source #
Constructors
BidiPairedBracketType |
Instances
Show BidiPairedBracketType_ Source # | |
Defined in Data.Text.ICU.Char Methods showsPrec :: Int -> BidiPairedBracketType_ -> ShowS # show :: BidiPairedBracketType_ -> String # showList :: [BidiPairedBracketType_] -> ShowS # | |
NFData BidiPairedBracketType_ Source # | |
Defined in Data.Text.ICU.Char Methods rnf :: BidiPairedBracketType_ -> () # | |
Property BidiPairedBracketType_ (Maybe BidiPairedBracketType) Source # | |
Defined in Data.Text.ICU.Char Methods fromNative :: BidiPairedBracketType_ -> Int32 -> Maybe BidiPairedBracketType toUProperty :: BidiPairedBracketType_ -> UProperty |
Property value types
Descriptions of Unicode blocks.
Constructors
Instances
Bounded BlockCode Source # | |
Enum BlockCode Source # | |
Defined in Data.Text.ICU.Char Methods succ :: BlockCode -> BlockCode # pred :: BlockCode -> BlockCode # fromEnum :: BlockCode -> Int # enumFrom :: BlockCode -> [BlockCode] # enumFromThen :: BlockCode -> BlockCode -> [BlockCode] # enumFromTo :: BlockCode -> BlockCode -> [BlockCode] # enumFromThenTo :: BlockCode -> BlockCode -> BlockCode -> [BlockCode] # | |
Eq BlockCode Source # | |
Show BlockCode Source # | |
NFData BlockCode Source # | |
Defined in Data.Text.ICU.Char | |
Property Block_ BlockCode Source # | |
Defined in Data.Text.ICU.Char |
The language directional property of a character set.
Constructors
Instances
Enum Direction Source # | |
Defined in Data.Text.ICU.Char Methods succ :: Direction -> Direction # pred :: Direction -> Direction # fromEnum :: Direction -> Int # enumFrom :: Direction -> [Direction] # enumFromThen :: Direction -> Direction -> [Direction] # enumFromTo :: Direction -> Direction -> [Direction] # enumFromThenTo :: Direction -> Direction -> Direction -> [Direction] # | |
Eq Direction Source # | |
Show Direction Source # | |
NFData Direction Source # | |
Defined in Data.Text.ICU.Char | |
Property BidiClass_ Direction Source # | |
Defined in Data.Text.ICU.Char |
data Decomposition Source #
Constructors
Canonical | |
Compat | |
Circle | |
Final | |
Font | |
Fraction | |
Initial | |
Isolated | |
Medial | |
Narrow | |
NoBreak | |
Small | |
Square | |
Sub | |
Super | |
Vertical | |
Wide | |
Count |
Instances
data EastAsianWidth Source #
Instances
data GeneralCategory Source #
Constructors
Instances
data HangulSyllableType Source #
Constructors
LeadingJamo | |
VowelJamo | |
TrailingJamo | |
LVSyllable | |
LVTSyllable |
Instances
data JoiningGroup Source #
Constructors
Instances
Enum JoiningGroup Source # | |
Defined in Data.Text.ICU.Char Methods succ :: JoiningGroup -> JoiningGroup # pred :: JoiningGroup -> JoiningGroup # toEnum :: Int -> JoiningGroup # fromEnum :: JoiningGroup -> Int # enumFrom :: JoiningGroup -> [JoiningGroup] # enumFromThen :: JoiningGroup -> JoiningGroup -> [JoiningGroup] # enumFromTo :: JoiningGroup -> JoiningGroup -> [JoiningGroup] # enumFromThenTo :: JoiningGroup -> JoiningGroup -> JoiningGroup -> [JoiningGroup] # | |
Eq JoiningGroup Source # | |
Defined in Data.Text.ICU.Char | |
Show JoiningGroup Source # | |
Defined in Data.Text.ICU.Char Methods showsPrec :: Int -> JoiningGroup -> ShowS # show :: JoiningGroup -> String # showList :: [JoiningGroup] -> ShowS # | |
NFData JoiningGroup Source # | |
Defined in Data.Text.ICU.Char Methods rnf :: JoiningGroup -> () # | |
Property JoiningGroup_ (Maybe JoiningGroup) Source # | |
Defined in Data.Text.ICU.Char Methods fromNative :: JoiningGroup_ -> Int32 -> Maybe JoiningGroup toUProperty :: JoiningGroup_ -> UProperty |
data JoiningType Source #
Constructors
JoinCausing | |
DualJoining | |
LeftJoining | |
RightJoining | |
Transparent |
Instances
Enum JoiningType Source # | |
Defined in Data.Text.ICU.Char Methods succ :: JoiningType -> JoiningType # pred :: JoiningType -> JoiningType # toEnum :: Int -> JoiningType # fromEnum :: JoiningType -> Int # enumFrom :: JoiningType -> [JoiningType] # enumFromThen :: JoiningType -> JoiningType -> [JoiningType] # enumFromTo :: JoiningType -> JoiningType -> [JoiningType] # enumFromThenTo :: JoiningType -> JoiningType -> JoiningType -> [JoiningType] # | |
Eq JoiningType Source # | |
Defined in Data.Text.ICU.Char | |
Show JoiningType Source # | |
Defined in Data.Text.ICU.Char Methods showsPrec :: Int -> JoiningType -> ShowS # show :: JoiningType -> String # showList :: [JoiningType] -> ShowS # | |
NFData JoiningType Source # | |
Defined in Data.Text.ICU.Char Methods rnf :: JoiningType -> () # | |
Property JoiningType_ (Maybe JoiningType) Source # | |
Defined in Data.Text.ICU.Char Methods fromNative :: JoiningType_ -> Int32 -> Maybe JoiningType toUProperty :: JoiningType_ -> UProperty |
data NumericType Source #
Instances
Enum NumericType Source # | |
Defined in Data.Text.ICU.Char Methods succ :: NumericType -> NumericType # pred :: NumericType -> NumericType # toEnum :: Int -> NumericType # fromEnum :: NumericType -> Int # enumFrom :: NumericType -> [NumericType] # enumFromThen :: NumericType -> NumericType -> [NumericType] # enumFromTo :: NumericType -> NumericType -> [NumericType] # enumFromThenTo :: NumericType -> NumericType -> NumericType -> [NumericType] # | |
Eq NumericType Source # | |
Defined in Data.Text.ICU.Char | |
Show NumericType Source # | |
Defined in Data.Text.ICU.Char Methods showsPrec :: Int -> NumericType -> ShowS # show :: NumericType -> String # showList :: [NumericType] -> ShowS # | |
NFData NumericType Source # | |
Defined in Data.Text.ICU.Char Methods rnf :: NumericType -> () # | |
Property NumericType_ (Maybe NumericType) Source # | |
Defined in Data.Text.ICU.Char Methods fromNative :: NumericType_ -> Int32 -> Maybe NumericType toUProperty :: NumericType_ -> UProperty |
Text boundaries
data GraphemeClusterBreak Source #
Instances
Constructors
Instances
Enum LineBreak Source # | |
Defined in Data.Text.ICU.Char Methods succ :: LineBreak -> LineBreak # pred :: LineBreak -> LineBreak # fromEnum :: LineBreak -> Int # enumFrom :: LineBreak -> [LineBreak] # enumFromThen :: LineBreak -> LineBreak -> [LineBreak] # enumFromTo :: LineBreak -> LineBreak -> [LineBreak] # enumFromThenTo :: LineBreak -> LineBreak -> LineBreak -> [LineBreak] # | |
Eq LineBreak Source # | |
Show LineBreak Source # | |
NFData LineBreak Source # | |
Defined in Data.Text.ICU.Char | |
Property LineBreak_ (Maybe LineBreak) Source # | |
Defined in Data.Text.ICU.Char |
data SentenceBreak Source #
Constructors
SBATerm | |
SBClose | |
SBFormat | |
SBLower | |
SBNumeric | |
SBOLetter | |
SBSep | |
SBSP | |
SBSTerm | |
SBUpper | |
SBCR | |
SBExtend | |
SBLF | |
SBSContinue |
Instances
Constructors
WBALetter | |
WBFormat | |
WBKatakana | |
WBMidLetter | |
WBMidNum | |
WBNumeric | |
WBExtendNumLet | |
WBCR | |
WBExtend | |
WBLF | |
WBMidNumLet | |
WBNewline | |
RegionalIndicator | |
HebrewLetter | |
SingleQuote | |
DoubleQuote |
Instances
Enum WordBreak Source # | |
Defined in Data.Text.ICU.Char Methods succ :: WordBreak -> WordBreak # pred :: WordBreak -> WordBreak # fromEnum :: WordBreak -> Int # enumFrom :: WordBreak -> [WordBreak] # enumFromThen :: WordBreak -> WordBreak -> [WordBreak] # enumFromTo :: WordBreak -> WordBreak -> [WordBreak] # enumFromThenTo :: WordBreak -> WordBreak -> WordBreak -> [WordBreak] # | |
Eq WordBreak Source # | |
Show WordBreak Source # | |
NFData WordBreak Source # | |
Defined in Data.Text.ICU.Char | |
Property WordBreak_ (Maybe WordBreak) Source # | |
Defined in Data.Text.ICU.Char |
data BidiPairedBracketType Source #
Instances
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 code point
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 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.
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.
combiningClass :: Char -> Int Source #
direction :: Char -> Direction Source #
Return the bidirectional category value for the code point, which is used in the Unicode bidirectional algorithm (UAX #9 http://www.unicode.org/reports/tr9/).
isMirrored :: Char -> Bool Source #
Determine whether the code point 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
.