hgmp: Haskell interface to GMP

[ bsd3, library, numeric ] [ Propose Tags ]

Currently, types and instances, and marshalling between Integer and Rational and the corresponding GMP types. That is, enough to allow FFI to GMP code (whether in GMP itself or in third-party code that uses GMP).

Supports only GHC with integer-gmp, this might change if there's any demand.


[Skip to Readme]

Downloads

Note: This package has metadata revisions in the cabal description newer than included in the tarball. To unpack the package including the revisions, use 'cabal get'.

Maintainer's Corner

Package maintainers

For package maintainers and hackage trustees

Candidates

  • No Candidates
Versions [RSS] 0.1.0.0, 0.1.0.1, 0.1.1, 0.1.2, 0.1.2.1
Change log CHANGELOG.md
Dependencies base (>=4.8 && <4.11), ghc-prim (>=0.4 && <0.6), integer-gmp (>=1.0 && <1.1) [details]
License BSD-3-Clause
Copyright 2016 Claude Heiland-Allen
Author Claude Heiland-Allen
Maintainer claude@mathr.co.uk
Revised Revision 1 made by ClaudeHeilandAllen at 2017-08-03T20:32:18Z
Category Numeric
Home page https://code.mathr.co.uk/hgmp
Source repo head: git clone https://code.mathr.co.uk/hgmp.git
this: git clone https://code.mathr.co.uk/hgmp.git(tag v0.1.0.1)
Uploaded by ClaudeHeilandAllen at 2016-08-10T04:39:21Z
Distributions Arch:0.1.2.1, NixOS:0.1.2.1
Reverse Dependencies 6 direct, 6 indirect [details]
Downloads 3861 total (46 in the last 30 days)
Rating 2.25 (votes: 2) [estimated by Bayesian average]
Your Rating
  • λ
  • λ
  • λ
Status Docs available [build log]
Last success reported on 2016-08-10 [all 1 reports]

Readme for hgmp-0.1.0.1

[back to package description]

hgmp

Haskell interface to GMP. 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