[Haskell-cafe] [ANN] hgmp-0.1.0.0

Claude Heiland-Allen claude at mathr.co.uk
Mon Aug 1 19:57:36 UTC 2016


Hi all,

hgmp 0.1.0.0 is released! [0]

hgmp is a Haskell interface to GMP[1] (for GHC with the default 
integer-gmp implementation of Integer). Contains type definitions and 
marshalling functions, to be able to write FFI bindings using Haskell's 
Integer and Rational types. Function bindings may come in a future version.

A simple example illustrating binding to GMP's next probable-prime function:

     {-# LANGUAGE ForeignFunctionInterface #-}

     import Foreign.Ptr (Ptr(..))
     import Numeric.GMP.Types (MPZ)
     import Numeric.GMP.Utils (withInInteger, withOutInteger_)
     import System.IO.Unsafe (unsafePerformIO)

     foreign import ccall safe "__gmpz_nextprime"
       mpz_nextprime :: Ptr MPZ -> Ptr MPZ -> IO ()

     nextPrime :: Integer -> Integer
     nextPrime n =
       unsafePerformIO $
         withOutInteger_ $ \rop ->
           withInInteger n $ \op ->
             mpz_nextprime rop op

You can cabal install (or otherwise get it) from Hackage[2], or get (or 
browse[3]) the freshest sources from git:

     git clone https://code.mathr.co.uk/hgmp.git

Any and all feedback welcome! I'm sure there are some things that could 
be improved, and ideas for future versions will be appreciated too.

[0] https://mathr.co.uk/blog/2016-08-01_hgmp_0_1_0_0_released.html
[1] https://gmplib.org/
[2] http://hackage.haskell.org/package/hgmp
[3] https://code.mathr.co.uk/hgmp

Thanks,


Claude
-- 
https://mathr.co.uk


More information about the Haskell-Cafe mailing list