normalization-insensitive-2.0.0.1: Normalization insensitive string comparison

Copyright(c) 2011-2013 Bas van Dijk
(c) 2016 Patrick Pelletier
LicenseBSD-style (see the file LICENSE)
MaintainerPatrick Pelletier <code@funwithsoftware.org>
Safe HaskellTrustworthy
LanguageHaskell98

Data.Unicode.NormalizationInsensitive

Description

This module is intended to be imported qualified. May I suggest:

import           Data.Unicode.NormalizationInsensitive  ( NI )
import qualified Data.Unicode.NormalizationInsensitive as NI

Synopsis

Documentation

data NI s Source #

A NI s provides Normalization Insensitive comparison for the string-like type s (for example: String, Text, ByteString, etc.).

Note that NI s has an instance for IsString which together with the OverloadedStrings language extension allows you to write normalization insensitive string literals as in:

> ("\12399\12441" :: NI Text) == ("\12400" :: NI Text)
True

Instances

Eq s => Eq (NI s) Source # 

Methods

(==) :: NI s -> NI s -> Bool #

(/=) :: NI s -> NI s -> Bool #

Data s => Data (NI s) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> NI s -> c (NI s) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (NI s) #

toConstr :: NI s -> Constr #

dataTypeOf :: NI s -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (NI s)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (NI s)) #

gmapT :: (forall b. Data b => b -> b) -> NI s -> NI s #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> NI s -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> NI s -> r #

gmapQ :: (forall d. Data d => d -> u) -> NI s -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> NI s -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> NI s -> m (NI s) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> NI s -> m (NI s) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> NI s -> m (NI s) #

Ord s => Ord (NI s) Source # 

Methods

compare :: NI s -> NI s -> Ordering #

(<) :: NI s -> NI s -> Bool #

(<=) :: NI s -> NI s -> Bool #

(>) :: NI s -> NI s -> Bool #

(>=) :: NI s -> NI s -> Bool #

max :: NI s -> NI s -> NI s #

min :: NI s -> NI s -> NI s #

(Read s, Normalizable s) => Read (NI s) Source # 
Show s => Show (NI s) Source # 

Methods

showsPrec :: Int -> NI s -> ShowS #

show :: NI s -> String #

showList :: [NI s] -> ShowS #

(IsString s, Normalizable s) => IsString (NI s) Source # 

Methods

fromString :: String -> NI s #

(Monoid s, Normalizable s) => Monoid (NI s) Source # 

Methods

mempty :: NI s #

mappend :: NI s -> NI s -> NI s #

mconcat :: [NI s] -> NI s #

NFData s => NFData (NI s) Source # 

Methods

rnf :: NI s -> () #

Hashable s => Hashable (NI s) Source # 

Methods

hashWithSalt :: Int -> NI s -> Int #

hash :: NI s -> Int #

Normalizable (NI s) Source # 

Methods

normalize :: NI s -> NI s Source #

mk :: Normalizable s => s -> NI s Source #

Make the given string-like value normalization insensitive.

original :: NI s -> s Source #

Retrieve the original string-like value.

map :: Normalizable s2 => (s1 -> s2) -> NI s1 -> NI s2 Source #

Transform the original string-like value but keep it normalized.

class Normalizable s where Source #

Class of string-like types that support normalization.

Minimal complete definition

normalize

Methods

normalize :: s -> s Source #

Instances

Normalizable String Source # 
Normalizable ByteString Source #

Note that normalize on ByteStrings assumes UTF-8 encoded strings!

Normalizable ByteString Source #

Note that normalize on ByteStrings assumes UTF-8 encoded strings!

Normalizable Text Source # 

Methods

normalize :: Text -> Text Source #

Normalizable Text Source # 

Methods

normalize :: Text -> Text Source #

Normalizable (NI s) Source # 

Methods

normalize :: NI s -> NI s Source #