{-# LANGUAGE ForeignFunctionInterface #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
module Data.Text.ICU.Iterator
(
CharIterator
, fromString
, fromText
, fromUtf8
) where
import Data.ByteString (ByteString)
import Data.Int (Int32)
import Data.Text (Text, pack)
import Data.Text.ICU.Internal (CharIterator(..), UCharIterator, asOrdering,
withCharIterator)
import Foreign.Ptr (Ptr)
import System.IO.Unsafe (unsafePerformIO)
instance Eq CharIterator where
CharIterator
a == :: CharIterator -> CharIterator -> Bool
== CharIterator
b = CharIterator -> CharIterator -> Ordering
compareIter CharIterator
a CharIterator
b forall a. Eq a => a -> a -> Bool
== Ordering
EQ
instance Ord CharIterator where
compare :: CharIterator -> CharIterator -> Ordering
compare = CharIterator -> CharIterator -> Ordering
compareIter
compareIter :: CharIterator -> CharIterator -> Ordering
compareIter :: CharIterator -> CharIterator -> Ordering
compareIter CharIterator
a CharIterator
b = forall a. IO a -> a
unsafePerformIO forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. Integral a => a -> Ordering
asOrdering forall b c a. (b -> c) -> (a -> b) -> a -> c
.
forall a. CharIterator -> (Ptr UCharIterator -> IO a) -> IO a
withCharIterator CharIterator
a forall a b. (a -> b) -> a -> b
$ forall a. CharIterator -> (Ptr UCharIterator -> IO a) -> IO a
withCharIterator CharIterator
b forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ptr UCharIterator -> Ptr UCharIterator -> IO Int32
u_strCompareIter
fromString :: String -> CharIterator
fromString :: String -> CharIterator
fromString = Text -> CharIterator
CIText forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
pack
{-# INLINE fromString #-}
fromText :: Text -> CharIterator
fromText :: Text -> CharIterator
fromText = Text -> CharIterator
CIText
{-# INLINE fromText #-}
fromUtf8 :: ByteString -> CharIterator
fromUtf8 :: ByteString -> CharIterator
fromUtf8 = ByteString -> CharIterator
CIUTF8
{-# INLINE fromUtf8 #-}
foreign import ccall unsafe "hs_text_icu.h __hs_u_strCompareIter" u_strCompareIter
:: Ptr UCharIterator -> Ptr UCharIterator -> IO Int32