{-# LANGUAGE DeriveDataTypeable, ForeignFunctionInterface #-}
module Data.Text.ICU.Collate.Pure
(
Collator
, collator
, collatorWith
, collate
, collateIter
, sortKey
, uca
) where
import Control.Monad (forM_)
import Data.ByteString (ByteString)
import Data.Text (Text)
import Data.Text.ICU.Collate.Internal (Collator(..))
import Data.Text.ICU.Internal (CharIterator, LocaleName(..))
import System.IO.Unsafe (unsafePerformIO)
import qualified Data.Text.ICU.Collate as IO
collator :: LocaleName -> Collator
collator :: LocaleName -> Collator
collator LocaleName
loc = IO Collator -> Collator
forall a. IO a -> a
unsafePerformIO (IO Collator -> Collator) -> IO Collator -> Collator
forall a b. (a -> b) -> a -> b
$ MCollator -> Collator
C (MCollator -> Collator) -> IO MCollator -> IO Collator
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap` LocaleName -> IO MCollator
IO.open LocaleName
loc
collatorWith :: LocaleName -> [IO.Attribute] -> Collator
collatorWith :: LocaleName -> [Attribute] -> Collator
collatorWith LocaleName
loc [Attribute]
atts = IO Collator -> Collator
forall a. IO a -> a
unsafePerformIO (IO Collator -> Collator) -> IO Collator -> Collator
forall a b. (a -> b) -> a -> b
$ do
MCollator
mc <- LocaleName -> IO MCollator
IO.open LocaleName
loc
[Attribute] -> (Attribute -> IO ()) -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
t a -> (a -> m b) -> m ()
forM_ [Attribute]
atts ((Attribute -> IO ()) -> IO ()) -> (Attribute -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ MCollator -> Attribute -> IO ()
IO.setAttribute MCollator
mc
Collator -> IO Collator
forall (m :: * -> *) a. Monad m => a -> m a
return (MCollator -> Collator
C MCollator
mc)
collate :: Collator -> Text -> Text -> Ordering
collate :: Collator -> Text -> Text -> Ordering
collate (C MCollator
c) Text
a Text
b = IO Ordering -> Ordering
forall a. IO a -> a
unsafePerformIO (IO Ordering -> Ordering) -> IO Ordering -> Ordering
forall a b. (a -> b) -> a -> b
$ MCollator -> Text -> Text -> IO Ordering
IO.collate MCollator
c Text
a Text
b
{-# INLINE collate #-}
collateIter :: Collator -> CharIterator -> CharIterator -> Ordering
collateIter :: Collator -> CharIterator -> CharIterator -> Ordering
collateIter (C MCollator
c) CharIterator
a CharIterator
b = IO Ordering -> Ordering
forall a. IO a -> a
unsafePerformIO (IO Ordering -> Ordering) -> IO Ordering -> Ordering
forall a b. (a -> b) -> a -> b
$ MCollator -> CharIterator -> CharIterator -> IO Ordering
IO.collateIter MCollator
c CharIterator
a CharIterator
b
{-# INLINE collateIter #-}
sortKey :: Collator -> Text -> ByteString
sortKey :: Collator -> Text -> ByteString
sortKey (C MCollator
c) = IO ByteString -> ByteString
forall a. IO a -> a
unsafePerformIO (IO ByteString -> ByteString)
-> (Text -> IO ByteString) -> Text -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MCollator -> Text -> IO ByteString
IO.sortKey MCollator
c
{-# INLINE sortKey #-}
uca :: Collator
uca :: Collator
uca = LocaleName -> Collator
collator LocaleName
Root
{-# NOINLINE uca #-}