{-# LINE 1 "Data/Text/ICU/CharsetDetection/Internal.hsc" #-}
{-# LANGUAGE DeriveDataTypeable, ForeignFunctionInterface, EmptyDataDecls #-}
module Data.Text.ICU.CharsetDetection.Internal
(
UCharsetDetector
, UCharsetMatch
, CharsetMatch(..)
, CharsetDetector(..)
, withCharsetDetector
, wrapUCharsetDetector
, wrapUCharsetMatch
, mkCharsetDetector
, withCharsetMatch
) where
import Data.Typeable (Typeable)
import Foreign.ForeignPtr (ForeignPtr, withForeignPtr)
import Foreign.Ptr (FunPtr, Ptr)
import Data.Text.ICU.Error.Internal (UErrorCode, handleError)
import Data.Text.ICU.Internal (newICUPtr)
data UCharsetDetector
data CharsetDetector = CharsetDetector {
charsetDetectorPtr :: {-# UNPACK #-} !(ForeignPtr UCharsetDetector)
} deriving (Typeable)
mkCharsetDetector :: IO CharsetDetector
mkCharsetDetector = wrapUCharsetDetector $ handleError ucsdet_open
withCharsetDetector :: CharsetDetector -> (Ptr UCharsetDetector -> IO a) -> IO a
withCharsetDetector (CharsetDetector ucsd) = withForeignPtr ucsd
{-# INLINE withCharsetDetector #-}
wrapUCharsetDetector :: IO (Ptr UCharsetDetector) -> IO CharsetDetector
wrapUCharsetDetector = newICUPtr CharsetDetector ucsdet_close
{-# INLINE wrapUCharsetDetector #-}
data UCharsetMatch
data CharsetMatch =
CharsetMatch
{ charsetMatchPtr :: {-# UNPACK #-} !(Ptr UCharsetMatch)
, charsetMatchDetector :: CharsetDetector
}
deriving (Typeable)
wrapUCharsetMatch :: CharsetDetector -> IO (Ptr UCharsetMatch) -> IO CharsetMatch
wrapUCharsetMatch cd = fmap $ flip CharsetMatch cd
withCharsetMatch :: CharsetMatch -> (Ptr UCharsetMatch -> IO a) -> IO a
withCharsetMatch (CharsetMatch ucsm _) f = f ucsm
foreign import ccall unsafe "hs_text_icu.h &__hs_ucsdet_close" ucsdet_close
:: FunPtr (Ptr UCharsetDetector -> IO ())
foreign import ccall unsafe "hs_text_icu.h __hs_ucsdet_open" ucsdet_open
:: Ptr UErrorCode -> IO (Ptr UCharsetDetector)