module Data.Unicode.NormalizationInsensitive.Internal ( NI
, mk
, unsafeMk
, original
, normalized
, map
, Normalizable(normalize)
) where
import Data.Eq ( Eq, (==) )
import Data.Function ( on )
import Data.Monoid ( Monoid, mempty, mappend )
import Data.Ord ( Ord, compare )
import Data.String ( IsString, fromString )
import Data.Data ( Data )
import Data.Typeable ( Typeable )
import Prelude ( String, (.), fmap )
import Text.Read ( Read, readPrec )
import Text.Show ( Show, showsPrec )
import qualified Data.ByteString as B ( ByteString )
import qualified Data.ByteString.Lazy as BL ( ByteString, fromStrict, toStrict )
import qualified Data.Text as T ( Text, pack, unpack )
import qualified Data.Text.Encoding as T ( decodeUtf8With, encodeUtf8 )
import qualified Data.Text.Encoding.Error as T ( lenientDecode )
import qualified Data.Text.Lazy as TL ( Text, fromStrict, toStrict )
import Control.DeepSeq ( NFData, rnf, deepseq )
import Data.Hashable ( Hashable, hashWithSalt )
import qualified Data.Text.Normalize as T ( normalize )
import Data.Unicode.Types ( NormalizationMode(NFC) )
data NI s = NI { original :: !s
, normalized :: !s
}
deriving (Data, Typeable)
mk :: Normalizable s => s -> NI s
mk s = NI s (normalize s)
unsafeMk :: s -> NI s
unsafeMk s = NI s s
map :: Normalizable s2 => (s1 -> s2) -> (NI s1 -> NI s2)
map f = mk . f . original
instance (IsString s, Normalizable s) => IsString (NI s) where
fromString = mk . fromString
instance (Monoid s, Normalizable s) => Monoid (NI s) where
mempty = NI mempty mempty
NI o1 _ `mappend` NI o2 _ = NI o12 (normalize o12)
where o12 = o1 `mappend` o2
instance Eq s => Eq (NI s) where
(==) = (==) `on` normalized
instance Ord s => Ord (NI s) where
compare = compare `on` normalized
instance (Read s, Normalizable s) => Read (NI s) where
readPrec = fmap mk readPrec
instance Show s => Show (NI s) where
showsPrec prec = showsPrec prec . original
instance Hashable s => Hashable (NI s) where
hashWithSalt salt = hashWithSalt salt . normalized
instance NFData s => NFData (NI s) where
rnf (NI o f) = o `deepseq` f `deepseq` ()
mode :: NormalizationMode
mode = NFC
class Normalizable s where
normalize :: s -> s
instance Normalizable B.ByteString where
normalize = T.encodeUtf8 . normalize . T.decodeUtf8With T.lenientDecode
instance Normalizable BL.ByteString where
normalize = BL.fromStrict . normalize . BL.toStrict
instance Normalizable String where
normalize = T.unpack . T.normalize mode . T.pack
instance Normalizable T.Text where
normalize = T.normalize mode
instance Normalizable TL.Text where
normalize = TL.fromStrict . T.normalize mode . TL.toStrict
instance Normalizable (NI s) where
normalize (NI _ l) = NI l l