{-# Language TemplateHaskell #-} {-| Module : Data.Text.ICU.Normalized.NFC Description: : NFC Text implementing the 'IsString' typeclass. Copyright : ©2016 License : GPL-3 Maintainer : Evan Cofsky Stability : experimental Portability : POSIX This will perform the NFC pass on any Text to ensure it's in a Normalized form to prevent subtle text-based bugs. Provides 'Ord' and 'Eq' based on 'ICU.uca'. Also derives 'Generic' and 'Typeable' for other packages to use. -} module Data.Text.ICU.Normalized.NFC ( NFCText, packed, builder, text, normalized ) where import qualified Data.Text.ICU.Normalize as ICU import Data.Text (Text) import qualified Data.Text.Lazy as LT import GHC.Generics (Generic) import Data.Text.Encoding (encodeUtf8, decodeUtf8) import qualified Data.ByteString.Char8 as C8 import Data.String (IsString(..)) import Text.ParserCombinators.ReadP import Text.Read hiding (get) import Prelude.Unicode import Data.Data import Data.Typeable import Control.Lens hiding (strict, lazy) import Data.ByteString (ByteString) import qualified Data.Text.Strict.Lens as DL import Data.Text.Lens (IsText(..)) -- | An NFC-normalized Data.Text newtype NFCText = NFCText {unNFC ∷ Text} deriving (Show, Generic, Data, Typeable) normalized ∷ Iso' NFCText Text normalized = iso (unNFC) (nnfc) instance IsText NFCText where -- | 'Iso' for packing and unpacking 'NFCText' from 'String'. packed = iso (nnfc ∘ view DL.packed) (review DL.packed ∘ unNFC) -- | 'Iso' between a 'Builder' and an 'NFCText' builder = iso (view DL.builder ∘ unNFC) (nnfc ∘ review DL.builder) -- | Normalizes Text to 'NFCText' -- 1. Do a 'quickCheck'. If this returns definitively, we normalize -- based on its response. -- 2. If not, we call 'isNormalized', and normalize based on its -- response. nnfc t = let nt = ICU.normalize ICU.NFC -- | If 'qc' fails to provide an answer we use 'isNormalized'. isn = if ICU.isNormalized ICU.NFC t then t else nt t -- | If we get a definitive answer from qc, act on it. quick t = ICU.quickCheck ICU.NFC t >>= \q → if q then return t else return $ nt t in NFCText $ case quick t of Nothing → isn Just q → q -- | Since we're NFC, we satisfy FCD, and we can just compare -- directly. instance Ord NFCText where (NFCText a) `compare` (NFCText b) = let cmp = ICU.compare [ICU.InputIsFCD] in a `cmp` b -- | If the Ord of the two texts is EQ, then they're equal. instance Eq NFCText where a == b = a `compare` b == EQ