Copyright | (c) Edward Kmett 2010-2012 |
---|---|
License | BSD3 |
Maintainer | ekmett@gmail.com |
Stability | experimental |
Portability | DeriveDataTypeable |
Safe Haskell | Safe |
Language | Haskell98 |
Provides unicode general categories, which are typically connoted by
\p{Ll}
or \p{Modifier_Letter}
. Lookups can be constructed using categories
or individual character sets can be used directly.
A case, _
and -
insensitive lookup is provided by lookupCategory
and can be used to provide behavior similar to that of Perl or PCRE.
Synopsis
- data Category = Category {}
- categories :: [Category]
- lookupCategory :: String -> Maybe Category
- lookupCategoryCharSet :: String -> Maybe CharSet
- modifierLetter :: CharSet
- otherLetter :: CharSet
- letter :: CharSet
- lowercaseLetter :: CharSet
- uppercaseLetter :: CharSet
- titlecaseLetter :: CharSet
- letterAnd :: CharSet
- nonSpacingMark :: CharSet
- spacingCombiningMark :: CharSet
- enclosingMark :: CharSet
- mark :: CharSet
- space :: CharSet
- lineSeparator :: CharSet
- paragraphSeparator :: CharSet
- separator :: CharSet
- mathSymbol :: CharSet
- currencySymbol :: CharSet
- modifierSymbol :: CharSet
- otherSymbol :: CharSet
- symbol :: CharSet
- decimalNumber :: CharSet
- letterNumber :: CharSet
- otherNumber :: CharSet
- number :: CharSet
- dashPunctuation :: CharSet
- openPunctuation :: CharSet
- closePunctuation :: CharSet
- initialQuote :: CharSet
- finalQuote :: CharSet
- connectorPunctuation :: CharSet
- otherPunctuation :: CharSet
- punctuation :: CharSet
- control :: CharSet
- format :: CharSet
- privateUse :: CharSet
- surrogate :: CharSet
- notAssigned :: CharSet
- other :: CharSet
Unicode General Category
Instances
Data Category Source # | |
Defined in Data.CharSet.Unicode.Category gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Category -> c Category # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Category # toConstr :: Category -> Constr # dataTypeOf :: Category -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Category) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Category) # gmapT :: (forall b. Data b => b -> b) -> Category -> Category # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Category -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Category -> r # gmapQ :: (forall d. Data d => d -> u) -> Category -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Category -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Category -> m Category # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Category -> m Category # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Category -> m Category # | |
Show Category Source # | |
Lookup
categories :: [Category] Source #
CharSets by Category
Letter
Letter&
Mark
Separator
Symbol
mathSymbol :: CharSet Source #
Number
Punctuation
finalQuote :: CharSet Source #
Other
privateUse :: CharSet Source #