{-# LINE 1 "Data/Text/ICU/Shape.hsc" #-}
{-# LANGUAGE CPP, ForeignFunctionInterface #-}
module Data.Text.ICU.Shape
(
shapeArabic
, ShapeOption(..)
) where
import Data.List (foldl')
import Data.Text.ICU.Error.Internal (UErrorCode, handleOverflowError)
import Data.Bits ((.|.))
import Data.Int (Int32)
import Foreign.Ptr (Ptr)
import Data.Text.ICU.Internal (UChar, useAsUCharPtr, fromUCharPtr)
import Data.Text (Text)
import System.IO.Unsafe (unsafePerformIO)
data ShapeOption =
AggregateTaskheel
| DigitTypeAnExtended
| DigitsAlen2AnInitAl
| DigitsAlen2AnInitLr
| DigitsAn2En
| DigitsEn2An
| LengthFixedSpacesAtBeginning
| LengthFixedSpacesAtEnd
| LengthFixedSpacesNear
| LettersShape
| LettersUnshape
| LettersShapeTashkeelIsolated
| PreservePresentation
| TextDirectionVisualLTR
deriving (Show)
reduceShapeOpts :: [ShapeOption] -> Int32
reduceShapeOpts = foldl' orO 0
where a `orO` b = a .|. fromShapeOption b
fromShapeOption :: ShapeOption -> Int32
fromShapeOption AggregateTaskheel = 16384
{-# LINE 72 "Data/Text/ICU/Shape.hsc" #-}
fromShapeOption DigitTypeAnExtended = 256
{-# LINE 73 "Data/Text/ICU/Shape.hsc" #-}
fromShapeOption DigitsAlen2AnInitAl = 128
{-# LINE 74 "Data/Text/ICU/Shape.hsc" #-}
fromShapeOption DigitsAlen2AnInitLr = 96
{-# LINE 75 "Data/Text/ICU/Shape.hsc" #-}
fromShapeOption DigitsAn2En = 64
{-# LINE 76 "Data/Text/ICU/Shape.hsc" #-}
fromShapeOption DigitsEn2An = 32
{-# LINE 77 "Data/Text/ICU/Shape.hsc" #-}
fromShapeOption LengthFixedSpacesAtBeginning = 3
{-# LINE 78 "Data/Text/ICU/Shape.hsc" #-}
fromShapeOption LengthFixedSpacesAtEnd = 2
{-# LINE 79 "Data/Text/ICU/Shape.hsc" #-}
fromShapeOption LengthFixedSpacesNear = 1
{-# LINE 80 "Data/Text/ICU/Shape.hsc" #-}
fromShapeOption LettersShape = 8
{-# LINE 81 "Data/Text/ICU/Shape.hsc" #-}
fromShapeOption LettersUnshape = 16
{-# LINE 82 "Data/Text/ICU/Shape.hsc" #-}
fromShapeOption LettersShapeTashkeelIsolated = 24
{-# LINE 83 "Data/Text/ICU/Shape.hsc" #-}
fromShapeOption PreservePresentation = 32768
{-# LINE 84 "Data/Text/ICU/Shape.hsc" #-}
fromShapeOption TextDirectionVisualLTR = 4
{-# LINE 85 "Data/Text/ICU/Shape.hsc" #-}
shapeArabic :: [ShapeOption] -> Text -> Text
shapeArabic options t = unsafePerformIO . useAsUCharPtr t $ \sptr slen ->
let slen' = fromIntegral slen
options' = reduceShapeOpts options
in handleOverflowError (fromIntegral slen)
(\dptr dlen -> u_shapeArabic sptr slen' dptr (fromIntegral dlen) options')
(\dptr dlen -> fromUCharPtr dptr (fromIntegral dlen))
foreign import ccall unsafe "hs_text_icu.h __hs_u_shapeArabic" u_shapeArabic
:: Ptr UChar -> Int32
-> Ptr UChar -> Int32
-> Int32 -> Ptr UErrorCode -> IO Int32