{-# LANGUAGE CPP, MagicHash, UnboxedTuples #-}
{-# OPTIONS_HADDOCK not-home #-}
module Data.Text.Internal.Unsafe
(
inlineInterleaveST
, inlinePerformIO
, unsafeWithForeignPtr
) where
import Foreign.Ptr (Ptr)
import Foreign.ForeignPtr (ForeignPtr)
#if MIN_VERSION_base(4,15,0)
import qualified GHC.ForeignPtr (unsafeWithForeignPtr)
#else
import qualified Foreign.ForeignPtr (withForeignPtr)
#endif
import GHC.ST (ST(..))
import GHC.IO (IO(IO))
import GHC.Base (realWorld#)
{-# INLINE inlinePerformIO #-}
inlinePerformIO :: IO a -> a
inlinePerformIO :: forall a. IO a -> a
inlinePerformIO (IO State# RealWorld -> (# State# RealWorld, a #)
m) = case State# RealWorld -> (# State# RealWorld, a #)
m State# RealWorld
realWorld# of (# State# RealWorld
_, a
r #) -> a
r
inlineInterleaveST :: ST s a -> ST s a
inlineInterleaveST :: forall s a. ST s a -> ST s a
inlineInterleaveST (ST STRep s a
m) = STRep s a -> ST s a
forall s a. STRep s a -> ST s a
ST (STRep s a -> ST s a) -> STRep s a -> ST s a
forall a b. (a -> b) -> a -> b
$ \ State# s
s ->
let r :: a
r = case STRep s a
m State# s
s of (# State# s
_, a
res #) -> a
res in (# State# s
s, a
r #)
{-# INLINE inlineInterleaveST #-}
unsafeWithForeignPtr :: ForeignPtr a -> (Ptr a -> IO b) -> IO b
#if MIN_VERSION_base(4,15,0)
unsafeWithForeignPtr :: forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
unsafeWithForeignPtr = ForeignPtr a -> (Ptr a -> IO b) -> IO b
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
GHC.ForeignPtr.unsafeWithForeignPtr
#else
unsafeWithForeignPtr = Foreign.ForeignPtr.withForeignPtr
#endif