{-# LANGUAGE DeriveDataTypeable, EmptyDataDecls, ForeignFunctionInterface #-}
module Data.Text.ICU.Collate.Internal
(
MCollator(..)
, Collator(..)
, UCollator
, withCollator
, wrap
) where
import Data.Typeable (Typeable)
import Foreign.ForeignPtr (ForeignPtr, withForeignPtr)
import Foreign.Ptr (FunPtr, Ptr)
import Data.Text.ICU.Internal (newICUPtr)
data UCollator
data MCollator = MCollator {-# UNPACK #-} !(ForeignPtr UCollator)
deriving (Typeable)
newtype Collator = C MCollator
deriving (Typeable)
withCollator :: MCollator -> (Ptr UCollator -> IO a) -> IO a
withCollator :: forall a. MCollator -> (Ptr UCollator -> IO a) -> IO a
withCollator (MCollator ForeignPtr UCollator
col) Ptr UCollator -> IO a
action = forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr UCollator
col Ptr UCollator -> IO a
action
{-# INLINE withCollator #-}
wrap :: IO (Ptr UCollator) -> IO MCollator
wrap :: IO (Ptr UCollator) -> IO MCollator
wrap = forall a i.
(ForeignPtr a -> i) -> FinalizerPtr a -> IO (Ptr a) -> IO i
newICUPtr ForeignPtr UCollator -> MCollator
MCollator FunPtr (Ptr UCollator -> IO ())
ucol_close
{-# INLINE wrap #-}
foreign import ccall unsafe "hs_text_icu.h &__hs_ucol_close" ucol_close
:: FunPtr (Ptr UCollator -> IO ())