module Graphics.Text.Font.Choose.Internal.FFI where import Data.MessagePack (MessagePack(fromObject), pack, unpack, Object(ObjectStr)) import Foreign.C.String (CString, withCString, peekCString) import Foreign.Ptr (Ptr) import Foreign.ForeignPtr (ForeignPtr, withForeignPtr) import Foreign.Storable (Storable(..)) import Foreign.Marshal.Alloc (alloca, free) import Data.Tuple (swap) import Graphics.Text.Font.Choose.Result (throwNull, FcException) import Data.Maybe (fromJust) import Text.Read (readMaybe) import Control.Exception (throw) import Data.ByteString.Unsafe (unsafeUseAsCStringLen, unsafePackMallocCStringLen) import Data.ByteString.Lazy (toStrict, fromStrict, ByteString) import qualified Data.Text as Txt import System.IO.Unsafe (unsafePerformIO) unpackWithErr :: MessagePack a => ByteString -> Maybe a unpackWithErr bs = case unpack bs of Just (ObjectStr err) | Just x <- (readMaybe $ Txt.unpack err :: Maybe FcException) -> throw x Just x -> fromObject x Nothing -> Nothing withMessageIO :: MessagePack a => (CString -> Int -> IO b) -> a -> IO b withMessageIO cb a = unsafeUseAsCStringLen (toStrict $ pack a) (uncurry cb) withMessage :: MessagePack a => (CString -> Int -> b) -> a -> b withMessage inner arg = unsafePerformIO $ withMessageIO (\x -> return . inner x) arg fromMessage :: MessagePack a => (Ptr Int -> CString) -> Maybe a fromMessage inner = unpackWithErr $ fromStrict $ unsafePerformIO $ do unsafePackMallocCStringLen . swap =<< withPtr (throwNull . inner) fromMessage0 :: MessagePack a => (Ptr Int -> CString) -> a fromMessage0 = fromJust . fromMessage fromMessageIO :: MessagePack a => (Ptr Int -> IO CString) -> IO (Maybe a) fromMessageIO inner = do (a, b) <- withPtr $ \ptr -> do throwNull =<< inner ptr bs <- unsafePackMallocCStringLen (b, a) return $ unpackWithErr $ fromStrict bs fromMessageIO0 :: MessagePack a => (Ptr Int -> IO CString) -> IO a fromMessageIO0 inner = fromJust <$> fromMessageIO inner withCString' :: (CString -> a) -> String -> a withCString' inner = unsafePerformIO . flip withCString (return . inner) peekCString' :: CString -> String peekCString' ptr = unsafePerformIO $ do ret <- peekCString ptr free ptr return ret withForeignPtr' :: (Ptr a -> b) -> ForeignPtr a -> b withForeignPtr' inner arg = unsafePerformIO $ withForeignPtr arg $ return . inner -- I don't want to pull in all of inline-c for this util! withPtr :: (Storable a) => (Ptr a -> IO b) -> IO (a, b) withPtr f = do alloca $ \ptr -> do x <- f ptr y <- peek ptr return (y, x)