Here’s the cleaned up version
module Help where
import Data.Word (Word32)
import Foreign.C (CString, CInt(..), withCString)
import Foreign.ForeignPtr (ForeignPtr, newForeignPtr, FinalizerPtr)
import Foreign.Marshal.Alloc (alloca)
import Foreign.Ptr (Ptr, FunPtr)
import Foreign.Storable (peek)
data BotanHashStruct
-- int botan_hash_init(botan_hash_t* hash, const char* hash_name, uint32_t flags)
foreign import ccall unsafe botan_hash_init :: Ptr (Ptr BotanHashStruct) -> CString -> Word32 -> IO CInt
-- int botan_hash_destroy(botan_hash_t hash)
foreign import ccall "&botan_hash_destroy" botan_hash_destroy_funptr :: FinalizerPtr BotanHashStruct
-- this is a cheat because it ignores the 'int' return on hash_destroy
newtype BotanHash = BotanHash (ForeignPtr BotanHashStruct)
throwBotan :: CInt -> IO a
throwBotan x = fail ("Botan error: " ++ show x) -- do something better here
newBotanHash :: String -> IO BotanHash
newBotanHash name =
alloca $ \outPtr ->
withCString name $ \namePtr ->
botan_hash_init outPtr namePtr 0 >>= \ret ->
if 0 /= ret then throwBotan ret else
peek outPtr >>= \out ->
newForeignPtr botan_hash_destroy_funptr out >>= \fp ->
pure (BotanHash fp)