{-# LINE 1 "Data/Text/ICU/Spoof.hsc" #-}
{-# LANGUAGE BangPatterns, CPP, DeriveDataTypeable, ForeignFunctionInterface,
OverloadedStrings, RecordWildCards, ScopedTypeVariables #-}
module Data.Text.ICU.Spoof
(
MSpoof
, OpenFromSourceParseError(..)
, SpoofCheck(..)
, SpoofCheckResult(..)
, RestrictionLevel(..)
, SkeletonTypeOverride(..)
, open
, openFromSerialized
, openFromSource
, getSkeleton
, getChecks
, setChecks
, getRestrictionLevel
, setRestrictionLevel
, getAllowedLocales
, setAllowedLocales
, areConfusable
, spoofCheck
, serialize
) where
import Control.Applicative
import Control.DeepSeq (NFData(..))
import Control.Exception (Exception, throwIO, catchJust)
import Data.Bits ((.&.))
import Data.ByteString (ByteString)
import Data.ByteString.Internal (create, memcpy, toForeignPtr)
import Data.ByteString.Unsafe (unsafeUseAsCStringLen)
import Data.Int (Int32)
import Data.List (intercalate)
import Data.Text (Text, pack, splitOn, strip, unpack)
import Data.Text.Foreign (fromPtr, useAsPtr)
import Data.Text.ICU.BitMask (ToBitMask, fromBitMask, highestValueInBitMask,
toBitMask)
import Data.Text.ICU.Spoof.Internal (MSpoof, USpoof, withSpoof, wrap,
wrapWithSerialized)
import Data.Text.ICU.Error (u_PARSE_ERROR)
import Data.Text.ICU.Error.Internal (UErrorCode, UParseError,
ParseError(..), handleError,
handleOverflowError, handleParseError)
import Data.Text.ICU.Internal (UChar)
import Data.Typeable (Typeable)
import Data.Word (Word8)
import Foreign.C.String (CString, peekCString, withCString)
import Foreign.Marshal.Utils (with)
import Foreign.Ptr (Ptr, castPtr, nullPtr, plusPtr)
import Foreign.Storable (peek)
import Foreign.ForeignPtr (withForeignPtr)
data SpoofCheck
= SingleScriptConfusable
| MixedScriptConfusable
| WholeScriptConfusable
| AnyCase
| RestrictionLevel
| Invisible
| CharLimit
| MixedNumbers
| AllChecks
| AuxInfo
deriving (Bounded, Enum, Eq, Show)
instance ToBitMask SpoofCheck where
toBitMask SingleScriptConfusable = 1
{-# LINE 168 "Data/Text/ICU/Spoof.hsc" #-}
toBitMask MixedScriptConfusable = 2
{-# LINE 169 "Data/Text/ICU/Spoof.hsc" #-}
toBitMask WholeScriptConfusable = 4
{-# LINE 170 "Data/Text/ICU/Spoof.hsc" #-}
toBitMask AnyCase = 8
{-# LINE 171 "Data/Text/ICU/Spoof.hsc" #-}
toBitMask RestrictionLevel = 16
{-# LINE 172 "Data/Text/ICU/Spoof.hsc" #-}
toBitMask Invisible = 32
{-# LINE 173 "Data/Text/ICU/Spoof.hsc" #-}
toBitMask CharLimit = 64
{-# LINE 174 "Data/Text/ICU/Spoof.hsc" #-}
toBitMask MixedNumbers = 128
{-# LINE 175 "Data/Text/ICU/Spoof.hsc" #-}
toBitMask AllChecks = 65535
{-# LINE 176 "Data/Text/ICU/Spoof.hsc" #-}
toBitMask AuxInfo = 1073741824
{-# LINE 177 "Data/Text/ICU/Spoof.hsc" #-}
type USpoofCheck = Int32
data RestrictionLevel
= ASCII
| SingleScriptRestrictive
| HighlyRestrictive
| ModeratelyRestrictive
| MinimallyRestrictive
| Unrestrictive
deriving (Bounded, Enum, Eq, Show)
instance ToBitMask RestrictionLevel where
toBitMask ASCII = 268435456
{-# LINE 203 "Data/Text/ICU/Spoof.hsc" #-}
toBitMask SingleScriptRestrictive = 536870912
{-# LINE 204 "Data/Text/ICU/Spoof.hsc" #-}
toBitMask HighlyRestrictive = 805306368
{-# LINE 205 "Data/Text/ICU/Spoof.hsc" #-}
toBitMask ModeratelyRestrictive = 1073741824
{-# LINE 206 "Data/Text/ICU/Spoof.hsc" #-}
toBitMask MinimallyRestrictive = 1342177280
{-# LINE 207 "Data/Text/ICU/Spoof.hsc" #-}
toBitMask Unrestrictive = 1610612736
{-# LINE 208 "Data/Text/ICU/Spoof.hsc" #-}
type URestrictionLevel = Int32
data SpoofCheckResult
= CheckOK
| CheckFailed [SpoofCheck]
| CheckFailedWithRestrictionLevel {
failedChecks :: [SpoofCheck]
, failedLevel :: RestrictionLevel
}
deriving (Eq, Show)
data SkeletonTypeOverride
= SkeletonSingleScript
| SkeletonAnyCase
deriving (Bounded, Enum, Eq, Show)
instance ToBitMask SkeletonTypeOverride where
toBitMask SkeletonSingleScript = 1
{-# LINE 240 "Data/Text/ICU/Spoof.hsc" #-}
toBitMask SkeletonAnyCase = 8
{-# LINE 241 "Data/Text/ICU/Spoof.hsc" #-}
type USkeletonTypeOverride = Int32
makeSpoofCheckResult :: USpoofCheck -> SpoofCheckResult
makeSpoofCheckResult c =
case c of
0 -> CheckOK
_ ->
case restrictionLevel of
Nothing -> CheckFailed spoofChecks
Just l -> CheckFailedWithRestrictionLevel spoofChecks l
where spoofChecks = fromBitMask $ fromIntegral $
c .&. 65535
{-# LINE 254 "Data/Text/ICU/Spoof.hsc" #-}
restrictionValue = c .&. 2130706432
{-# LINE 255 "Data/Text/ICU/Spoof.hsc" #-}
restrictionLevel = highestValueInBitMask $ fromIntegral $
restrictionValue
data OpenFromSourceParseErrorFile =
ConfusablesTxtError | ConfusablesWholeScriptTxtError
deriving (Eq, Show)
instance NFData OpenFromSourceParseErrorFile where
rnf !_ = ()
data OpenFromSourceParseError = OpenFromSourceParseError {
errFile :: OpenFromSourceParseErrorFile
, parseError :: ParseError
} deriving (Show, Typeable)
instance NFData OpenFromSourceParseError where
rnf OpenFromSourceParseError{..} = rnf parseError `seq` rnf errFile
instance Exception OpenFromSourceParseError
open :: IO MSpoof
open = wrap =<< handleError uspoof_open
isParseError :: ParseError -> Maybe ParseError
isParseError = Just
openFromSource :: (ByteString, ByteString) -> IO MSpoof
openFromSource (confusables, confusablesWholeScript) =
unsafeUseAsCStringLen confusables $ \(cptr, clen) ->
unsafeUseAsCStringLen confusablesWholeScript $ \(wptr, wlen) ->
with 0 $ \errTypePtr ->
catchJust
isParseError
(wrap =<< (handleParseError
(== u_PARSE_ERROR)
(uspoof_openFromSource cptr (fromIntegral clen) wptr
(fromIntegral wlen) errTypePtr)))
(throwOpenFromSourceParseError errTypePtr)
throwOpenFromSourceParseError :: Ptr Int32 -> ParseError -> IO a
throwOpenFromSourceParseError errTypePtr parseErr = do
errType <- peek errTypePtr
let errFile =
if errType == 1
{-# LINE 309 "Data/Text/ICU/Spoof.hsc" #-}
then ConfusablesTxtError
else ConfusablesWholeScriptTxtError
throwIO $! OpenFromSourceParseError errFile parseErr
openFromSerialized :: ByteString -> IO MSpoof
openFromSerialized b =
case toForeignPtr b of
(ptr, off, len) -> withForeignPtr ptr $ \p ->
wrapWithSerialized ptr =<< handleError
(uspoof_openFromSerialized (p `plusPtr` off) (fromIntegral len) nullPtr)
getChecks :: MSpoof -> IO [SpoofCheck]
getChecks s = withSpoof s $ \sptr ->
(fromBitMask . fromIntegral . (.&.) 65535) <$>
{-# LINE 329 "Data/Text/ICU/Spoof.hsc" #-}
handleError (uspoof_getChecks sptr)
setChecks :: MSpoof -> [SpoofCheck] -> IO ()
setChecks s c = withSpoof s $ \sptr ->
handleError $ uspoof_setChecks sptr . fromIntegral $ toBitMask c
getRestrictionLevel :: MSpoof -> IO (Maybe RestrictionLevel)
getRestrictionLevel s = withSpoof s $ \sptr ->
(highestValueInBitMask . fromIntegral) <$> uspoof_getRestrictionLevel sptr
setRestrictionLevel :: MSpoof -> RestrictionLevel -> IO ()
setRestrictionLevel s l = withSpoof s $ \sptr ->
uspoof_setRestrictionLevel sptr . fromIntegral $ toBitMask l
getAllowedLocales :: MSpoof -> IO [String]
getAllowedLocales s = withSpoof s $ \sptr ->
splitLocales <$> (peekCString =<< handleError (uspoof_getAllowedLocales sptr))
where splitLocales = fmap (unpack . strip) . splitOn "," . pack
setAllowedLocales :: MSpoof -> [String] -> IO ()
setAllowedLocales s locs = withSpoof s $ \sptr ->
withCString (intercalate "," locs) $ \lptr ->
handleError (uspoof_setAllowedLocales sptr lptr)
areConfusable :: MSpoof -> Text -> Text -> IO SpoofCheckResult
areConfusable s t1 t2 = withSpoof s $ \sptr ->
useAsPtr t1 $ \t1ptr t1len ->
useAsPtr t2 $ \t2ptr t2len ->
makeSpoofCheckResult <$>
handleError (uspoof_areConfusable sptr
t1ptr (fromIntegral t1len)
t2ptr (fromIntegral t2len))
getSkeleton :: MSpoof -> Maybe SkeletonTypeOverride -> Text -> IO Text
getSkeleton s o t = withSpoof s $ \sptr ->
useAsPtr t $ \tptr tlen ->
handleOverflowError (fromIntegral tlen)
(\dptr dlen -> uspoof_getSkeleton sptr oflags tptr
(fromIntegral tlen) dptr (fromIntegral dlen))
(\dptr dlen -> fromPtr (castPtr dptr) (fromIntegral dlen))
where oflags = maybe 0 (fromIntegral . toBitMask) o
spoofCheck :: MSpoof -> Text -> IO SpoofCheckResult
spoofCheck s t = withSpoof s $ \sptr ->
useAsPtr t $ \tptr tlen ->
makeSpoofCheckResult <$> handleError
(uspoof_check sptr tptr (fromIntegral tlen) nullPtr)
serialize :: MSpoof -> IO ByteString
serialize s = withSpoof s $ \sptr ->
handleOverflowError 0
(\dptr dlen -> (uspoof_serialize sptr dptr (fromIntegral dlen)))
(\dptr dlen -> create (fromIntegral dlen) $ \bptr ->
memcpy dptr bptr (fromIntegral dlen))
foreign import ccall unsafe "hs_text_icu.h __hs_uspoof_open" uspoof_open
:: Ptr UErrorCode -> IO (Ptr USpoof)
foreign import ccall unsafe "hs_text_icu.h __hs_uspoof_openFromSerialized"
uspoof_openFromSerialized
:: Ptr Word8 -> Int32 -> Ptr Int32 -> Ptr UErrorCode -> IO (Ptr USpoof)
foreign import ccall unsafe "hs_text_icu.h __hs_uspoof_openFromSource"
uspoof_openFromSource
:: CString -> Int32 -> CString -> Int32 -> Ptr Int32 -> Ptr UParseError ->
Ptr UErrorCode -> IO (Ptr USpoof)
foreign import ccall unsafe "hs_text_icu.h __hs_uspoof_getChecks"
uspoof_getChecks
:: Ptr USpoof -> Ptr UErrorCode -> IO USpoofCheck
foreign import ccall unsafe "hs_text_icu.h __hs_uspoof_setChecks"
uspoof_setChecks
:: Ptr USpoof -> USpoofCheck -> Ptr UErrorCode -> IO ()
foreign import ccall unsafe "hs_text_icu.h __hs_uspoof_getRestrictionLevel"
uspoof_getRestrictionLevel
:: Ptr USpoof -> IO URestrictionLevel
foreign import ccall unsafe "hs_text_icu.h __hs_uspoof_setRestrictionLevel"
uspoof_setRestrictionLevel
:: Ptr USpoof -> URestrictionLevel -> IO ()
foreign import ccall unsafe "hs_text_icu.h __hs_uspoof_getAllowedLocales"
uspoof_getAllowedLocales
:: Ptr USpoof -> Ptr UErrorCode -> IO CString
foreign import ccall unsafe "hs_text_icu.h __hs_uspoof_setAllowedLocales"
uspoof_setAllowedLocales
:: Ptr USpoof -> CString -> Ptr UErrorCode -> IO ()
foreign import ccall unsafe "hs_text_icu.h __hs_uspoof_areConfusable"
uspoof_areConfusable
:: Ptr USpoof -> Ptr UChar -> Int32 -> Ptr UChar -> Int32 -> Ptr UErrorCode
-> IO USpoofCheck
foreign import ccall unsafe "hs_text_icu.h __hs_uspoof_check" uspoof_check
:: Ptr USpoof -> Ptr UChar -> Int32 -> Ptr Int32 -> Ptr UErrorCode
-> IO USpoofCheck
foreign import ccall unsafe "hs_text_icu.h __hs_uspoof_getSkeleton"
uspoof_getSkeleton
:: Ptr USpoof -> USkeletonTypeOverride -> Ptr UChar -> Int32 -> Ptr UChar ->
Int32 -> Ptr UErrorCode -> IO Int32
foreign import ccall unsafe "hs_text_icu.h __hs_uspoof_serialize"
uspoof_serialize
:: Ptr USpoof -> Ptr Word8 -> Int32 -> Ptr UErrorCode -> IO Int32