Skip to content

Instantly share code, notes, and snippets.

@zcourts
Last active January 3, 2016 14:39
Show Gist options
  • Save zcourts/8477405 to your computer and use it in GitHub Desktop.
Save zcourts/8477405 to your computer and use it in GitHub Desktop.
To wrap the ansi C fn void MurmurHash3_x86_32 (const void *key, int len, uint32_t seed, void *out);
{-# LANGUAGE ForeignFunctionInterface #-}
module Data.Dish.Murmur3(x86_32
--,x86_128,x64_128
) where
import Foreign.C -- get the C types
import Foreign.Ptr
import Foreign
import qualified Foreign.ForeignPtr.Unsafe as US
foreign import ccall "MurmurHash3_x86_32" c_x86_32
:: Ptr CString -> CInt -> CUInt -> Ptr CString -> ()
x86_32 :: String -> Int -> IO String
x86_32 val seed = do
val' <- withCAStringLen val $ \x -> return x
let strPtr = strFromCStr val'
let strLength = strLFromCStr val'
p <- mallocForeignPtr :: IO(ForeignPtr CString )
rt <- mallocForeignPtr :: IO(ForeignPtr CString )
withForeignPtr p $ \ptr -> poke ptr strPtr
withForeignPtr p $
\ptr -> return $
c_x86_32 ptr strLength (fromIntegral seed) $ US.unsafeForeignPtrToPtr rt
withForeignPtr rt $ \ ptr -> do cs <- peek ptr; peekCString cs
where strFromCStr :: CStringLen -> CString
strFromCStr = fst
strLFromCStr :: CStringLen -> CInt
strLFromCStr i = fromIntegral $ snd i
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment