unicode-data-0.4.0.1: Access Unicode Character Database (UCD)
Copyright(c) 2020 Composewell Technologies and Contributors
LicenseApache-2.0
Maintainerstreamly@composewell.com
Stabilityexperimental
Safe HaskellSafe-Inferred
LanguageHaskell2010

Unicode.Char.Case

Description

Case and case mapping related functions.

This module provides full predicates and mappings that are not compatible with those in Data.Char, which rely on simple properties. See Unicode.Char.Case.Compat for a drop-in replacement of the functions in Data.Char.

Synopsis

Predicates

isLowerCase :: Char -> Bool Source #

Returns True for lower-case characters.

It uses the character property Lowercase.

Since: 0.3.0

isLower :: Char -> Bool Source #

Deprecated: Use isLowerCase instead. Note that the behavior of this function does not match base:Data.Char.isLower. See Unicode.Char.Case.Compat for behavior compatible with base:Data.Char.

Returns True for lower-case characters.

It uses the character property Lowercase.

Since: 0.1.0

isUpperCase :: Char -> Bool Source #

Returns True for upper-case characters.

It uses the character property Uppercase.

Note: it does not match title-cased letters. Those are matched using: generalCategory c == TitlecaseLetter.

Since: 0.3.0

isUpper :: Char -> Bool Source #

Deprecated: Use isUpperCase instead. Note that the behavior of this function does not match base:Data.Char.isUpper. See Unicode.Char.Case.Compat for behavior compatible with base:Data.Char.

Returns True for upper-case characters.

It uses the character property Uppercase.

Note: it does not match title-cased letters. Those are matched using: generalCategory c == TitlecaseLetter.

Since: 0.1.0

Case mappings

Correct case conversion rules may map one input character to two or three output characters. For examples, see the documentation of toCaseFoldString, toLowerString, toTitleString and toUpperString.

Note: In some languages, case conversion is a locale- and context-dependent operation. The case conversion functions in this module are not locale nor context sensitive.

Case folding mapping

caseFoldMapping :: Unfold Char Char Source #

Returns the full folded case mapping of a character if the character is changed, else nothing.

It uses the character property Case_Folding.

Since: 0.3.1

toCaseFoldString :: Char -> String Source #

Convert a character to full folded case if defined, else to itself.

This function is mainly useful for performing caseless (also known as case insensitive) string comparisons.

A string x is a caseless match for a string y if and only if:

foldMap toCaseFoldString x == foldMap toCaseFoldString y

The result string may have more than one character, and may differ from applying toLowerString to the input string. For instance, “ﬓ” (U+FB13 Armenian small ligature men now) is case folded to the sequence “մ” (U+0574 Armenian small letter men) followed by “ն” (U+0576 Armenian small letter now), while “µ” (U+00B5 micro sign) is case folded to “μ” (U+03BC Greek small letter mu) instead of itself.

It uses the character property Case_Folding.

toCaseFoldString c == foldMap toCaseFoldString (toCaseFoldString c)

Since: 0.3.1

Lower case mapping

lowerCaseMapping :: Unfold Char Char Source #

Returns the full lower case mapping of a character if the character is changed, else nothing.

It uses the character property Lowercase_Mapping.

Since: 0.3.1

toLowerString :: Char -> String Source #

Convert a character to full lower case if defined, else to itself.

The result string may have more than one character. For instance, “İ” (U+0130 Latin capital letter I with dot above) maps to the sequence: “i” (U+0069 Latin small letter I) followed by “ ̇” (U+0307 combining dot above).

It uses the character property Lowercase_Mapping.

See: toLower for simple lower case conversion.

toLowerString c == foldMap toLowerString (toLowerString c)

Since: 0.3.1

Title case mapping

titleCaseMapping :: Unfold Char Char Source #

Returns the full title case mapping of a character if the character is changed, else nothing.

It uses the character property Titlecase_Mapping.

Since: 0.3.1

toTitleString :: Char -> String Source #

Convert a character to full title case if defined, else to itself.

The result string may have more than one character. For instance, “fl” (U+FB02 Latin small ligature FL) is converted to the sequence: “F” (U+0046 Latin capital letter F) followed by “l” (U+006C Latin small letter L).

It uses the character property Titlecase_Mapping.

See: toTitle for simple title case conversion.

Since: 0.3.1

Upper case mapping

upperCaseMapping :: Unfold Char Char Source #

Returns the full upper case mapping of a character if the character is changed, else nothing.

It uses the character property Uppercase_Mapping.

Since: 0.3.1

toUpperString :: Char -> String Source #

Convert a character to full upper case if defined, else to itself.

The result string may have more than one character. For instance, the German “ß” (U+00DF Eszett) maps to the two-letter sequence “SS”.

It uses the character property Uppercase_Mapping.

See: toUpper for simple upper case conversion.

toUpperString c == foldMap toUpperString (toUpperString c)

Since: 0.3.1

Unfold

data Unfold a b Source #

An Unfold a b is a generator of a stream of values of type b from a seed of type a.

Since: 0.3.1

Constructors

forall s. Unfold 

Fields

  • (s -> Step s b)

    Step function: compute the next step from the current one.

  • (a -> Step s b)

    Inject function: initialize the state with a seed value.

data Step s a Source #

A stream is a succession of Steps.

Since: 0.3.1

Constructors

Yield !a !s

Produces a single value and the next state of the stream.

Stop

Indicates there are no more values in the stream.

Instances

Instances details
Functor (Step s) Source # 
Instance details

Defined in Unicode.Internal.Unfold

Methods

fmap :: (a -> b) -> Step s a -> Step s b #

(<$) :: a -> Step s b -> Step s a #