-- {-# OPTIONS_GHC -funfolding-fun-discount=90 #-}
-- |
-- Module      : Data.Text.Normalize
-- Copyright   : (c) 2016 Harendra Kumar
--
-- License     : BSD-3-Clause
-- Maintainer  : harendra.kumar@gmail.com
-- Stability   : experimental
-- Portability : GHC
--
-- Unicode normalization for @Text@ data type.
--
module Data.Text.Normalize
    (
    -- * Normalization Modes
      NormalizationMode(..)
    -- * Normalization API
    , normalize
    ) where

import Data.Text (Text)
import Data.Unicode.Types (NormalizationMode(..))

-- Internal modules
import Data.Unicode.Internal.NormalizeStream
    ( DecomposeMode(..)
    , stream
    , unstream
    , unstreamC
    )

-- | Perform Unicode normalization on @Text@ according to the specified
-- normalization mode.
normalize :: NormalizationMode -> Text -> Text
normalize :: NormalizationMode -> Text -> Text
normalize NormalizationMode
mode =
    case NormalizationMode
mode of
      NormalizationMode
NFD  -> (DecomposeMode -> Stream Char -> Text
unstream DecomposeMode
Canonical)   (Stream Char -> Text) -> (Text -> Stream Char) -> Text -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Stream Char
stream
      NormalizationMode
NFKD -> (DecomposeMode -> Stream Char -> Text
unstream DecomposeMode
Kompat)  (Stream Char -> Text) -> (Text -> Stream Char) -> Text -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Stream Char
stream
      NormalizationMode
NFC  -> (DecomposeMode -> Stream Char -> Text
unstreamC DecomposeMode
Canonical)  (Stream Char -> Text) -> (Text -> Stream Char) -> Text -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Stream Char
stream
      NormalizationMode
NFKC -> (DecomposeMode -> Stream Char -> Text
unstreamC DecomposeMode
Kompat) (Stream Char -> Text) -> (Text -> Stream Char) -> Text -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Stream Char
stream