module Text.HyperEstraier.Utils ( withUTF8CString , withUTF8CString' , packMallocUTF8CString , peekUTF8CString , marshalOpts , withArrayOfPtrs ) where import Codec.Binary.UTF8.String import Data.Bits import Foreign.C.String import Foreign.Marshal.Alloc import Foreign.Marshal.Array import Foreign.Ptr -- Yet another withUTF8CString. Hope GHC officially supports this! withUTF8CString :: String -> (CString -> IO a) -> IO a withUTF8CString = withCString . encodeString withUTF8CString' :: Maybe String -> (CString -> IO a) -> IO a withUTF8CString' (Just str) f = withCString (encodeString str) f withUTF8CString' Nothing f = f nullPtr packMallocUTF8CString :: CString -> IO String packMallocUTF8CString cstr = do str <- return . decodeString =<< peekCString cstr free cstr return str peekUTF8CString :: CString -> IO String peekUTF8CString = fmap decodeString . peekCString marshalOpts :: Bits b => (a -> b) -> [a] -> b marshalOpts = (foldl (.|.) 0 .) . map withArrayOfPtrs :: (a -> (Ptr b -> IO c) -> IO c) -> [a] -> (Ptr (Ptr b) -> IO c) -> IO c withArrayOfPtrs withXPtr xs f = withXPtrList xs [] $ flip withArray f where -- withXPtrList :: [a] -> [Ptr b] -> ([Ptr b] -> IO c) -> IO c withXPtrList [] acc g = g acc withXPtrList (y:ys) acc g = withXPtr y $ \ xPtr -> withXPtrList ys (acc ++ [xPtr]) g