Copyright | (c) Edward Kmett 2010-2011 |
---|---|
License | BSD3 |
Maintainer | ekmett@gmail.com |
Stability | experimental |
Portability | portable |
Safe Haskell | Safe |
Language | Haskell98 |
Provides unicode general categories, which are typically connoted by
p{InBasicLatin}
or p{InIPA_Extensions}
. Lookups can be constructed using categories
or individual character sets can be used directly.
Synopsis
- data Block = Block {}
- blocks :: [Block]
- lookupBlock :: String -> Maybe Block
- lookupBlockCharSet :: String -> Maybe CharSet
- basicLatin :: CharSet
- latin1Supplement :: CharSet
- latinExtendedA :: CharSet
- latinExtendedB :: CharSet
- ipaExtensions :: CharSet
- spacingModifierLetters :: CharSet
- combiningDiacriticalMarks :: CharSet
- greekAndCoptic :: CharSet
- cyrillic :: CharSet
- cyrillicSupplementary :: CharSet
- armenian :: CharSet
- hebrew :: CharSet
- arabic :: CharSet
- syriac :: CharSet
- thaana :: CharSet
- devanagari :: CharSet
- bengali :: CharSet
- gurmukhi :: CharSet
- gujarati :: CharSet
- oriya :: CharSet
- tamil :: CharSet
- telugu :: CharSet
- kannada :: CharSet
- malayalam :: CharSet
- sinhala :: CharSet
- thai :: CharSet
- lao :: CharSet
- tibetan :: CharSet
- myanmar :: CharSet
- georgian :: CharSet
- hangulJamo :: CharSet
- ethiopic :: CharSet
- cherokee :: CharSet
- unifiedCanadianAboriginalSyllabics :: CharSet
- ogham :: CharSet
- runic :: CharSet
- tagalog :: CharSet
- hanunoo :: CharSet
- buhid :: CharSet
- tagbanwa :: CharSet
- khmer :: CharSet
- mongolian :: CharSet
- limbu :: CharSet
- taiLe :: CharSet
- khmerSymbols :: CharSet
- phoneticExtensions :: CharSet
- latinExtendedAdditional :: CharSet
- greekExtended :: CharSet
- generalPunctuation :: CharSet
- superscriptsAndSubscripts :: CharSet
- currencySymbols :: CharSet
- combiningDiacriticalMarksForSymbols :: CharSet
- letterlikeSymbols :: CharSet
- numberForms :: CharSet
- arrows :: CharSet
- mathematicalOperators :: CharSet
- miscellaneousTechnical :: CharSet
- controlPictures :: CharSet
- opticalCharacterRecognition :: CharSet
- enclosedAlphanumerics :: CharSet
- boxDrawing :: CharSet
- blockElements :: CharSet
- geometricShapes :: CharSet
- miscellaneousSymbols :: CharSet
- dingbats :: CharSet
- miscellaneousMathematicalSymbolsA :: CharSet
- supplementalArrowsA :: CharSet
- braillePatterns :: CharSet
- supplementalArrowsB :: CharSet
- miscellaneousMathematicalSymbolsB :: CharSet
- supplementalMathematicalOperators :: CharSet
- miscellaneousSymbolsAndArrows :: CharSet
- cjkRadicalsSupplement :: CharSet
- kangxiRadicals :: CharSet
- ideographicDescriptionCharacters :: CharSet
- cjkSymbolsAndPunctuation :: CharSet
- hiragana :: CharSet
- katakana :: CharSet
- bopomofo :: CharSet
- hangulCompatibilityJamo :: CharSet
- kanbun :: CharSet
- bopomofoExtended :: CharSet
- katakanaPhoneticExtensions :: CharSet
- enclosedCjkLettersAndMonths :: CharSet
- cjkCompatibility :: CharSet
- cjkUnifiedIdeographsExtensionA :: CharSet
- yijingHexagramSymbols :: CharSet
- cjkUnifiedIdeographs :: CharSet
- yiSyllables :: CharSet
- yiRadicals :: CharSet
- hangulSyllables :: CharSet
- highSurrogates :: CharSet
- highPrivateUseSurrogates :: CharSet
- lowSurrogates :: CharSet
- privateUseArea :: CharSet
- cjkCompatibilityIdeographs :: CharSet
- alphabeticPresentationForms :: CharSet
- arabicPresentationFormsA :: CharSet
- variationSelectors :: CharSet
- combiningHalfMarks :: CharSet
- cjkCompatibilityForms :: CharSet
- smallFormVariants :: CharSet
- arabicPresentationFormsB :: CharSet
- halfwidthAndFullwidthForms :: CharSet
- specials :: CharSet
Unicode General Category
Block | |
|
Instances
Data Block Source # | |
Defined in Data.CharSet.Unicode.Block gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Block -> c Block # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Block # dataTypeOf :: Block -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Block) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Block) # gmapT :: (forall b. Data b => b -> b) -> Block -> Block # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Block -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Block -> r # gmapQ :: (forall d. Data d => d -> u) -> Block -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Block -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Block -> m Block # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Block -> m Block # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Block -> m Block # | |
Show Block Source # | |
Lookup
CharSets by Block
basicLatin :: CharSet Source #
devanagari :: CharSet Source #
hangulJamo :: CharSet Source #
boxDrawing :: CharSet Source #
yiRadicals :: CharSet Source #