{-# LINE 1 "Data/Text/ICU/BiDi.hsc" #-}
{-# LANGUAGE ForeignFunctionInterface #-}
module Data.Text.ICU.BiDi
(
BiDi
, open
, openSized
, setPara
, setLine
, countParagraphs
, getParagraphByIndex
, getProcessedLength
, writeReordered
, WriteOption(..)
, reorderParagraphs
) where
import Data.Text.ICU.BiDi.Internal
import Foreign.Marshal.Utils (with)
import Foreign.Storable (peek)
import Foreign.Ptr (FunPtr, Ptr)
import Data.Int (Int32, Int16)
import Data.Text.ICU.Error.Internal (UErrorCode, handleError, handleOverflowError)
import Data.Text (Text)
import Data.Text.ICU.Internal (UChar, useAsUCharPtr, fromUCharPtr, newICUPtr)
import Foreign.C.Types (CInt(..))
import Data.List (foldl')
import Data.Bits ((.|.))
import System.IO.Unsafe (unsafePerformIO)
import Data.Traversable (for)
open :: IO BiDi
open = newICUPtr BiDi ubidi_close ubidi_open
openSized ::
Int32
-> Int32
-> IO BiDi
openSized maxlen maxruncount =
newICUPtr BiDi ubidi_close $ handleError (ubidi_openSized maxlen maxruncount)
setPara ::
BiDi
-> Text
-> Int32
-> IO ()
setPara bidi t paraLevel =
withBiDi bidi $ \bptr ->
useAsUCharPtr t $ \sptr slen -> handleError (ubidi_setPara bptr sptr (fromIntegral slen) paraLevel)
setLine ::
BiDi
-> Int32
-> Int32
-> BiDi
-> IO ()
setLine paraBidi start limit lineBidi =
withBiDi paraBidi $ \paraptr ->
withBiDi lineBidi $ \lineptr ->
handleError (ubidi_setLine paraptr start limit lineptr)
countParagraphs :: BiDi -> IO Int32
countParagraphs bidi = withBiDi bidi ubidi_countParagraphs
getParagraphByIndex ::
BiDi
-> Int32
-> IO (Int32, Int32)
getParagraphByIndex bidi paraIndex =
withBiDi bidi $ \bptr ->
with 0 $ \pstart ->
with 0 $ \pend -> do
handleError (ubidi_getParagraphByIndex bptr paraIndex pstart pend)
(,) <$> (fromIntegral <$> peek pstart)
<*> (fromIntegral <$> peek pend)
getProcessedLength :: BiDi -> IO Int32
getProcessedLength bidi = withBiDi bidi ubidi_getProcessedLength
data WriteOption =
DoMirroring
| InsertLrmForNumeric
| KeepBaseCombining
| OutputReverse
| RemoveBidiControls
deriving (Show)
reduceWriteOpts :: [WriteOption] -> Int16
reduceWriteOpts = foldl' orO 0
where a `orO` b = a .|. fromWriteOption b
fromWriteOption :: WriteOption -> Int16
fromWriteOption DoMirroring = 2
{-# LINE 134 "Data/Text/ICU/BiDi.hsc" #-}
fromWriteOption InsertLrmForNumeric = 4
{-# LINE 135 "Data/Text/ICU/BiDi.hsc" #-}
fromWriteOption KeepBaseCombining = 1
{-# LINE 136 "Data/Text/ICU/BiDi.hsc" #-}
fromWriteOption OutputReverse = 16
{-# LINE 137 "Data/Text/ICU/BiDi.hsc" #-}
fromWriteOption RemoveBidiControls = 8
{-# LINE 138 "Data/Text/ICU/BiDi.hsc" #-}
writeReordered :: BiDi -> [WriteOption] -> IO Text
writeReordered bidi opts = do
destLen <- getProcessedLength bidi
let options' = reduceWriteOpts opts
withBiDi bidi $ \bptr ->
handleOverflowError (fromIntegral destLen)
(\dptr dlen -> ubidi_writeReordered bptr dptr (fromIntegral dlen) options')
(\dptr dlen -> fromUCharPtr dptr (fromIntegral dlen))
foreign import ccall unsafe "hs_text_icu.h __hs_ubidi_open" ubidi_open
:: IO (Ptr UBiDi)
foreign import ccall unsafe "hs_text_icu.h __hs_ubidi_openSized" ubidi_openSized
:: Int32 -> Int32 -> Ptr UErrorCode -> IO (Ptr UBiDi)
foreign import ccall unsafe "hs_text_icu.h &__hs_ubidi_close" ubidi_close
:: FunPtr (Ptr UBiDi -> IO ())
foreign import ccall unsafe "hs_text_icu.h __hs_ubidi_setPara" ubidi_setPara
:: Ptr UBiDi -> Ptr UChar -> Int32 -> Int32 -> Ptr UErrorCode -> IO ()
foreign import ccall unsafe "hs_text_icu.h __hs_ubidi_countParagraphs" ubidi_countParagraphs
:: Ptr UBiDi -> IO Int32
foreign import ccall unsafe "hs_text_icu.h __hs_ubidi_getParagraphByIndex" ubidi_getParagraphByIndex
:: Ptr UBiDi -> Int32 -> Ptr CInt -> Ptr CInt -> Ptr UErrorCode -> IO ()
foreign import ccall unsafe "hs_text_icu.h __hs_ubidi_getProcessedLength" ubidi_getProcessedLength
:: Ptr UBiDi -> IO Int32
foreign import ccall unsafe "hs_text_icu.h __hs_ubidi_writeReordered" ubidi_writeReordered
:: Ptr UBiDi -> Ptr UChar -> Int32 -> Int16 -> Ptr UErrorCode -> IO Int32
foreign import ccall unsafe "hs_text_icu.h __hs_ubidi_setLine" ubidi_setLine
:: Ptr UBiDi -> Int32 -> Int32 -> Ptr UBiDi -> Ptr UErrorCode -> IO ()
reorderParagraphs :: [WriteOption] -> Text -> [Text]
reorderParagraphs options input =
unsafePerformIO $ do
bidi <- open
setPara bidi input 0
pcount <- countParagraphs bidi
lineBidi <- open
for [0..pcount-1] $ \pidx -> do
(start,limit) <- getParagraphByIndex bidi pidx
setLine bidi start limit lineBidi
writeReordered lineBidi options