{-# LANGUAGE DeriveDataTypeable, EmptyDataDecls, ForeignFunctionInterface #-}
module Data.Text.ICU.Spoof.Internal
(
MSpoof(..)
, Spoof(..)
, USpoof
, withSpoof
, wrap
, wrapWithSerialized
) where
import Data.Typeable (Typeable)
import Data.Word (Word8)
import Foreign.ForeignPtr (ForeignPtr, withForeignPtr)
import Foreign.Ptr (FunPtr, Ptr)
import Data.Text.ICU.Internal (newICUPtr)
data USpoof
data MSpoof = MSpoof {
MSpoof -> Maybe (ForeignPtr Word8)
serializedBuf :: Maybe (ForeignPtr Word8)
, MSpoof -> ForeignPtr USpoof
spoofPtr :: {-# UNPACK #-} !(ForeignPtr USpoof)
} deriving (Typeable)
newtype Spoof = S MSpoof
deriving (Typeable)
withSpoof :: MSpoof -> (Ptr USpoof -> IO a) -> IO a
withSpoof :: forall a. MSpoof -> (Ptr USpoof -> IO a) -> IO a
withSpoof (MSpoof Maybe (ForeignPtr Word8)
_ ForeignPtr USpoof
spoof) = forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr USpoof
spoof
{-# INLINE withSpoof #-}
wrap :: IO (Ptr USpoof) -> IO MSpoof
wrap :: IO (Ptr USpoof) -> IO MSpoof
wrap = forall a i.
(ForeignPtr a -> i) -> FinalizerPtr a -> IO (Ptr a) -> IO i
newICUPtr (Maybe (ForeignPtr Word8) -> ForeignPtr USpoof -> MSpoof
MSpoof forall a. Maybe a
Nothing) FunPtr (Ptr USpoof -> IO ())
uspoof_close
{-# INLINE wrap #-}
wrapWithSerialized :: ForeignPtr Word8 -> IO (Ptr USpoof) -> IO MSpoof
wrapWithSerialized :: ForeignPtr Word8 -> IO (Ptr USpoof) -> IO MSpoof
wrapWithSerialized ForeignPtr Word8
s = forall a i.
(ForeignPtr a -> i) -> FinalizerPtr a -> IO (Ptr a) -> IO i
newICUPtr (Maybe (ForeignPtr Word8) -> ForeignPtr USpoof -> MSpoof
MSpoof forall a b. (a -> b) -> a -> b
$ forall a. a -> Maybe a
Just ForeignPtr Word8
s) FunPtr (Ptr USpoof -> IO ())
uspoof_close
{-# INLINE wrapWithSerialized #-}
foreign import ccall unsafe "hs_text_icu.h &__hs_uspoof_close" uspoof_close
:: FunPtr (Ptr USpoof -> IO ())