
Esa, In the July thread, (Repost) Replacement for GMP as Bignum: ARPREC? Haskell?; OS X and OpenSSL, you wrote:
In past, I tried to get rid of GMP by replacing it with libtommath http://math.libtomcrypt.com/ But I have given up for now - because of related and unrelated problems.
Since I had no prior experience with LibTomMath I decided to take a look at it. The most recent release version of LibTomMath seems to be 0.39. Were some of the "related problems" you ran into due to bugs in an earlier version of LibTomMath? Maybe it is premature for me to go looking at replacing Integer when GHC has already moved so far ahead of itself I have to service the source code just to get it to build on OS X, but I figure that while I have the hood up I might as well take a look at the rest of the engine... If you have any old notes on the problems you encountered, I would greatly appreciate it. -Pete Tanski

Hi Peter, Peter Tanski wrote:
In the July thread, (Repost) Replacement for GMP as Bignum: ARPREC? Haskell?; OS X and OpenSSL, you wrote:
In past, I tried to get rid of GMP by replacing it with libtommath http://math.libtomcrypt.com/ But I have given up for now - because of related and unrelated problems.
Since I had no prior experience with LibTomMath I decided to take a look at it. The most recent release version of LibTomMath seems to be 0.39. Were some of the "related problems" you ran into due to bugs in an earlier version of LibTomMath? Maybe it is premature for me to go looking at replacing Integer when GHC has already moved so far ahead of itself I have to service the source code just to get it to build on OS X, but I figure that while I have the hood up I might as well take a look at the rest of the engine... If you have any old notes on the problems you encountered, I would greatly appreciate it.
What I have written here might not be the most useful guide to start with, but maybe it is of help for other interested souls. My first and foremost problem was that I had certain amount time I was going to use on it and that I use Windows, where ghc build breaks pretty often - and it was very badly broken at the time. I simply ran out of time and motivation. The resistance I met in community (irc mainly) for this step was also annoying. I also went wrong way when I started and added configure-option, but Simon Marlow (iirc) asked me not to add configure option, but to obliterate gmp alltogether. The big steps, to get things done, in this matter are: * Understanding how memory handling between math lib and GC works * Understanding some C-- * Understanding autotools and makefile hackery If you are new to ghc source, you should read (some of) http://hackage.haskell.org/trac/ghc/ and http://darcs.haskell.org/ghc/HACKING Most of the code for this task is fairly easy, actually. The bad thing is that it cannot be easily split into many small steps. Most of the task has very small scope: Most of the backend doesn't care, we just use exising bits, frontend and base-package don't see much or any diffrence. I'll add here some notes that might be helpful (but as I type these out of memory, they might not be 100% accurate): * The memory handling: The idea on most bignum libs is that they have c-structure kinda like this: struct Big { word size, used; digits* payload; bool sign; } ; Now, the size and used tell how much memory is allocated for paylod and how much of it is used. sign is the sign (plus/minus). payload is a pointer to memory that contains Integer decoded. Normally, in c, you would reuse these variables, but with immutability, we can't do that. This is handled in GHC so that payload (and sign) are stored in a bytearray, which is native garbage collectable type. It natively contains size. Before we call math-lib, we put together a temporary structure with correct pointers. As for target variable, we have hooked the mathlibs memory allocation functions to allocate correctly. Upon returning Integer, we just take payload, write sign on correct place and return the payload-pointer (possibly adjusted). In pseudo C digits* add(digits* din) { Big in, out; in.size=getLength(din); in.used=getLength(din); in.payload=din; in.sign=getSign(din); math_lib_init(out); math_lib_add(out, in); writeSign(out.payload, out.sign); return out.payload; } There are tricky parts for 64bit-stuff in 32bit systems and some floating point decoding uses bad configure-stuff that depends on math lib stuff, but mostly it's very boring hundreds of lines of C-- (but you can make the job much easier by using preprocessor). This is why APPREC might be hard - you need to know the internal representation. * C-- and related RTS stuff C-- is pretty easy, you should read C-- spec at cminusminus.org. GHC C-- unfortunately is not really near the C-- spec, it doesn't first of all implement it all - but that doesn't matter for this task - and then it has some extensions for casting and structure reading, I think. When removing GMP, it is easy to spot places that needs corresponding declrations/definitions for new math-lib instead of GMP. Reading old GMP primops, where most of the interesting c-- code is at, should also make it clearer - after a while, atleast. * Autotools and makefiles What a mess. Well, it always is for big projects. The annoying thing here for LibTomMath was that I found out, I'd need to add autotool configure-hackery into ghc and make internal libtommath dependant on it, so that digit-size and such were the size of native "word" on each machine. There's also a lot of DLL-related stuff in makefiles, which, I think, can safely be removed - some of it is wrong and outdated, so when/if it gets waken up, it needs to be rewritten anyway. GMP has it's own configure-script and it's invoked from the makefiles. To take on this task, I wouldn't say huge knowledge on ghc internals is required, but some knowledge on memory handling and low-level (near asm) programming is useful. Haskell knowledge for most part is not required. Fast machine is useful, but tweaking build options and having a good book/movies/other machine gets it done. It'd be very very useful to have 64-bit platform (in practice 64bit linux ia32_64) for testing. I'd say OS X is not a good platform to do this devel on, but I might be wrong on that. Linux being best tested OS, it is the most safe bet. I'd need to get rid of GMP, and if I can help (short of putting weeks worth of hours into) just shout. HTH, --Esa

Esa,
What I have written here might not be the most useful guide to start with, but maybe it is of help for other interested souls.
Many thanks for the notes; it would probably be better if more than one programmer worked on it.
* The memory handling: The idea on most bignum libs is that they have c-structure kinda like this: struct Big { word size, used; digits* payload; bool sign; } ; Now, the size and used tell how much memory is allocated for payload and how much of it is used. sign is the sign (plus/minus). payload is a pointer to memory that contains Integer decoded.
... Before we ... call math-lib, we put together a temporary structure with correct pointers. As for target variable, we have hooked the mathlibs memory allocation functions to allocate correctly. Upon returning Integer, we just take payload, write sign on correct place and return the payload-pointer (possibly adjusted).
In pseudo C digits* add(digits* din) { Big in, out; in.size=getLength(din); in.used=getLength(din); in.payload=din; in.sign=getSign(din); math_lib_init(out); math_lib_add(out, in); writeSign(out.payload, out.sign); return out.payload; }
Sorry to take more of your time, but what do you mean by allocate "correctly?" (This may sound naieve): the in { size, used, payload, sign } are all parts of the info-table for the payload and the RTS re-initialises the mathlib on each invocation, right? In the thread "returning to cost of Integer", John Meacham wrote:
we could use the standard GMP that comes with the system since ForeignPtr will take care of GCing Integers itself.
From current discussion: at present the allocation is done on the GC heap, when it could be done entirely by the mathlib. The benefit to letting the mathlib handle memory would be that you could use the mathlib with another (non-Haskell) part of your program at the same time (see, e.g., (bug) Ticket #311). (I am making an educated guess, here.) You probably chose to allocate GMP's memory on the GC heap because: (1) call-outs to another program are inherently impure since the type- system and execution order are not defined by the Haskell Runtime; and, (2) it was a stable way to ensure that the allocated memory would remain available to the thunk for lazy evaluation, i.e., so that the evaluation of the returned Bignum could be postponed indefinitely, correct? Or could the evaluation itself be postponed until the value was called for--making operations on Integers and other Bignums lazy? In other words, it does not seem possible to simply hold a ForeignPtr to the returned value unless there were a way to release the memory when it was no longer needed. If you wanted the mathlib to retain the value on behalf of GHC, you would have to modify the library itself. In the end you have a specialized version of the library and a change to the procedure from: math_lib_init ; ... return out.payload ; to: math_lib_init ; math_lib_evaluate ; math_lib_free ; An easier though less-efficient alternative would be to have GHC copy the value returned by the mathlib. That would be stable and allow other systems to use the same mathlib concurrently (assuming the lib is thread-safe). The third alternative I suggested previously was to embed the Bignum processing in GHC itself. I think it would be very difficult to maintain a solution that was both optimised and portable, at least in C--. (I may be way-off here; I am simply going by a rudimentary knowledge of BLAST implementations.) If I am correct about (2) above, the best conclusion I could draw from this is that the easiest solution would be to copy the memory on return from the mathlib.
There are tricky parts for 64bit-stuff in 32bit systems and some floating point decoding uses bad configure-stuff that depends on math lib stuff, but mostly it's very boring hundreds of lines of C-- (but you can make the job much easier by using preprocessor).
I was reading through the Makefiles and headers in ghc's main include directory about this. One of the big ToDo's seems to be to correct the method of configuring this stuff using machdep.h or the equivalent on a local system, such as the sysctl-headers on Darwin. For C-- this seems like it would be a bit more difficult than simply confirming whether (or how) the C implementation conforms to the current standard through the usual header system.
This is why APPREC might be hard - you need to know the internal representation.
GHC C-- unfortunately is not really near the C-- spec, it doesn't first of all implement it all - but that doesn't matter for this task - and then it has some extensions for casting and structure reading, I think.
These are really great suggestions. GHC's codes (including the .cmm files) seem very well commented.
Fast machine is useful, but tweaking build options and having a good book/movies/other machine gets it done. It'd be very very useful to have 64-bit platform (in practice 64bit linux ia32_64) for testing. I'd say OS X is not a good platform to do this devel on, but I might be wrong on that. Linux being best tested OS, it is the most safe bet.
Yes, I have a slow machine to work with but that just means I have more incentive to think carefully before I try something out. The 64bit part is a problem but that should be well-handled if the configuration mess could be cleaned up. I have 32bit Linux and Windows systems I can use (both very slow, as well) but if the fix holds to the standards it should work... I am not sure yet, but I might make it easier on myself by cleaning up the configuration; the move was to Cabalize GHC, but I think that goal was for the Haskell code since the rest would have to remain in scripts, anyway. Would it be simpler to move to a more configurable system like Bakefile or Scons for putting a heterogeneous construction together? Best regards, Peter

Hi Peter, Peter Tanski wrote:
(This may sound naieve): the in { size, used, payload, sign } are all parts of the info-table for the payload and the RTS re-initialises the mathlib on each invocation, right?
I hope my answer helps, but if it gets you more confused, maybe it's just because I'm confused...I'm certainly not the best qualified to answer. Infotables are static as far as I understand. I was also a bit wrong, now that I read primops-code again. (Places of code that I read for this: http://darcs.haskell.org/ghc/rts/PrimOps.cmm search for #define GMP_TAKE_RET1 for an example of macro that is used to implement unary op. http://darcs.haskell.org/packages/base/GHC/Num.lhs search for data Integer) The interesting ctor for Integer is: | J# Int# ByteArray# Here we see that J# has two params size (which also contains sign) of the data pointer to another object, garbage-collection managed bytearray In GMP_TAKE1_RET1 we have MP_INT__mp_alloc(mp_tmp1) = W_TO_INT(StgArrWords_words(d1)); MP_INT__mp_size(mp_tmp1) = (s1); MP_INT__mp_d(mp_tmp1) = BYTE_ARR_CTS(d1); Where s1 and d1 are the parameters from that constructor. In GMP's case, size variable contains sign, and no sign variable is needed. Payload is the actual bytes in bytearray-object and allocated size is the amount of bytes allocated for bytearray-object. Because the memory allocation for GMP has been hijacked, we can simply return the important bits. RET_NP( TO_W_(MP_INT__mp_size(mp_result1)), MP_INT__mp_d(mp_result1) - SIZEOF_StgArrWords); RET_NP jumps back, or into, whatever needs the answer, we return two things, int that has the size and sign from GMP structure, and pointer to bytearray object - we need to adjust the pointer location to point into bytearray-object, instead of it's payload. The return type is actually, (# Int#, ByteArray# #), which is unboxed tuple containing unboxed Int and pointer/reference to ByteArray-object.
In the thread "returning to cost of Integer", John Meacham wrote:
we could use the standard GMP that comes with the system since ForeignPtr will take care of GCing Integers itself.
From current discussion: at present the allocation is done on the GC heap, when it could be done entirely by the mathlib. The benefit to letting the mathlib handle memory would be that you could use the mathlib with another (non-Haskell) part of your program at the same time (see, e.g., (bug) Ticket #311).
There are other nicer things about that as well - untying Integer (atleast mostly) from runtime/frontend and moving it more into domain of libraries.
(I am making an educated guess, here.) You probably chose to allocate GMP's memory on the GC heap because:
(I have no idea about original reasons.)
(1) call-outs to another program are inherently impure since the type-system and execution order are not defined by the Haskell Runtime; and,
Another program? I assume you meant outside pure haskell - "call-outs" have side-effects. We can get around by using unsafePerformIO, which doesn't really differ that much from writing it in C-- (and library in C), except we'd write haskell.
(2) it was a stable way to ensure that the allocated memory would remain available to the thunk for lazy evaluation, i.e., so that the evaluation of the returned Bignum could be postponed indefinitely, correct? Or could the evaluation itself be postponed until the value was called for--making operations on Integers and other Bignums lazy?
Uhm, naturally, haskell rts needs to control lifetime of the memory. I am not sure what you're trying to say here, really. Is the point that we cannot free almost anything without permission from garbage collector? Because, yeah, we can't. My guess (without having read the thread you mention) is that using ForeignPtrs brings two cons: Possibly extra indirection and using lots of Integers will mean (in many cases) a lots of finalisers that get run, and running finalisers (and checking for them in the first place) might be slow.
In other words, it does not seem possible to simply hold a ForeignPtr to the returned value unless there were a way to release the memory when it was no longer needed. If you wanted the mathlib to retain the value on behalf of GHC, you would have to modify the library itself. In the end you have a specialized version of the library and a change to the procedure from: math_lib_init ; ... return out.payload ; to: math_lib_init ; math_lib_evaluate ; math_lib_free ;
Only temporaries could be free'd here. Anything else could be needed again.
An easier though less-efficient alternative would be to have GHC copy the value returned by the mathlib. That would be stable and allow other systems to use the same mathlib concurrently (assuming the lib is thread-safe).
As I understand, you suggest here copying payload instead of merging memory handling. I don't think it's clearly, if ever, less efficient than ForeignPtr-based approach. But I'd guess it is *more* code than current solution.
The third alternative I suggested previously was to embed the Bignum processing in GHC itself. I think it would be very difficult to maintain a solution that was both optimised and portable, at least in C--. (I may be way-off here; I am simply going by a rudimentary knowledge of BLAST implementations.)
I don't think it differs much from doing the same in C. It does seem shame to write bignum in C--, as we don't get many elegance-style advantages from writing it in C-- instead of C.
If I am correct about (2) above, the best conclusion I could draw from this is that the easiest solution would be to copy the memory on return from the mathlib.
Depends what your goals are. If you don't care about GMP being rendered unavailable to other non-haskell parts of the program, the current solution is one of the easiest. The easiest solution must be either writing bignum in haskell or using ForeignPtrs.
directory about this. One of the big ToDo's seems to be to correct the method of configuring this stuff using machdep.h or the equivalent on a local system, such as the sysctl-headers on Darwin. For C-- this seems like it would be a bit more difficult than simply confirming whether (or how) the C implementation conforms to the current standard through the usual header system.
Neither C or C-- was meant to be used to detect what system can do. It is simply a byproduct, which autotools takes to the extreme. C does fit the bill better because there's so much framework built for it, mainly because unixy OSes, and their kernels, are written in C. As for what it has to do with topic at hand, I have no idea. C-- is simply used as an intermediate language for the compiler, for convience of calling conventions and such, some low-level operations are written in it. [snip lots more] There's lots thoughts, but I found I had little to say about those, sorry. Best regards, --Esa

Hey Esa, Another great instructive email! Thanks again! I will keep this response short because I am sure you are busy and you have been more than helpful so far. I also need to get back to working through the code...
I hope my answer helps, but if it gets you more confused, maybe it's just because I'm confused...
No, you are just trying to understand what I am saying and since I am new to GHC's rts internals I do not yet have the knowledge to express my thoughts well.
There are other nicer things about that as well - untying Integer (atleast mostly) from runtime/frontend and moving it more into domain of libraries.
<snip>
Another program? I assume you meant outside pure haskell - "call- outs" have side-effects. We can get around by using unsafePerformIO, which doesn't really differ that much from writing it in C-- (and library in C), except we'd write haskell.
If the program (written in C--, C, C++, whatever) and the interface from Haskell to that program were well-typed it would not be any different than writing the entire program in Haskell, but the order of execution must remain in sync with the Haskell program. If the rts is threaded or parallel you might imagine problems cropping up. In this case I have to evaluate whether, say, OpenSSL's BN library is threaded (or, for Parallel Haskell, also working through PVM), not merely thread safe and certainly not merely reentrant.
Uhm, naturally, haskell rts needs to control lifetime of the memory. I am not sure what you're trying to say here, really. Is the point that we cannot free almost anything without permission from garbage collector? Because, yeah, we can't.
My problem was not with the garbage collector but with what the garbage collector depends on: when an object is evaluated and no longer in scope. I am not insane enough to attempt writing high level mathematical operations such as pow() or sqrt() as primitives in an integrated Bignum implementation, but you might be able to imagine that at that level it would be possible to choose when to save and when to evaluate parts of a long equation.
As I understand, you suggest here copying payload instead of merging memory handling. I don't think it's clearly, if ever, less efficient than ForeignPtr-based approach. But I'd guess it is *more* code than current solution.
Excellent point.
The third alternative I suggested previously was to embed the Bignum processing in GHC itself. I think it would be very difficult to maintain a solution that was both optimised and portable, at least in C--. (I may be way-off here; I am simply going by a rudimentary knowledge of BLAST implementations.)
I don't think it differs much from doing the same in C. It does seem shame to write bignum in C--, as we don't get many elegance-style advantages from writing it in C-- instead of C.
<cut and paste from below>
As for what it has to do with topic at hand, I have no idea. C-- is simply used as an intermediate language for the compiler, for convience of calling conventions and such, some low-level operations are written in it.
When I mentioned BLAS (not "BLAST", sorry) implementations I meant that--as I understand it--some may contain hand-optimised code written in assembler. Certainly I would personally prefer implementing something in C but as you noted C-- allows GHC more convenience. C-- may also allow GHC to manipulate fragments and produce native code in ways that may not be possible to express in C, including the Bignum implementation. I don't know whether GHC takes - fasm to this extent, that is, further than patching object code from a Bignum library, but that I think that is one of the long-term goals.
... One of the big ToDo's seems to be to correct the method of configuring this stuff using machdep.h or the equivalent on a local system, such as the sysctl-headers on Darwin. For C-- this seems like it would be a bit more difficult than simply confirming whether (or how) the C implementation conforms to the current standard through the usual header system.
Neither C or C-- was meant to be used to detect what system can do. It is simply a byproduct, which autotools takes to the extreme.
I meant that the autotools determine the correct configuration--the big ToDo--and that C or C-- code must be written to conform to the configuration that the autotools found. C would certainly be the easiest; C-- would mean reaching deep into the specs. C would also open the possibility for optimisations from compilers and system libraries that would not be available to C--. One more reason to use a separate Bignum library... Best regards, Peter

Esa, Peter Thank you for diving into the GMP stuff. Simon and I discussed it a bit; here's a summary: (1) We'd be delighted to use a BSD-licensed alternative to GMP in GHC. It's been a long-standing issue, just never quite important enough to get done. If either or both of you are willing to put in the legwork, and emerge with an implementation that we understand and can maintain, we'd be happy to use it. We'll certainly help in any way we can. (2) We're concerned about performance. Replacing GMP, but losing substantial performance on bignum-intensive programs would be unattractive. (3) It's unlikely (albeit not impossible) that we'll get GMP-level performance out of a Haskell-only bignum library. Nevertheless, providing such a library would be a particularly easy way to provide a drop-in alternative to GMP. It's just that it probably wouldn't let us *replace* GMP altogether, for performance reasons, so we'd still need the GMP route; from a maintenance point of view, this would be a step backwards! (4) The tricky spot for any library is memory allocation. Our GMP-based implementation works by getting GMP to use GHC's allocator to allocate memory. This means that every bignum is allocated in the Haskell heap, is automatically managed by GHC's garbage collector, which is Very Good. But because the allocator is statically linked to GMP, you can only have one allocator, and that leads to difficulties if you have another bit of the same binary that also wants to use GMP. (Of course, we could *copy* GMP, changing all the function names. That would eliminate the problem!) I suppose that one alternative is to let the library use 'malloc', but make a foreign-pointer proxy for every bignum, which calls 'free' when the GHC garbage collector frees it. Not as efficient, though. Anyway, this problem will arise for *any* bignum library, and is one of the first things to figure out. (5) If you do go ahead, could you pls start a Wiki page on the GHC development Wiki (http://hackage.haskell.org/trac/ghc), where you document your thoughts, the evolving design etc? You might want to extract the core of this email thread to initialise the Wiki page. Thanks for your help! Simon

Hello Simon, Wednesday, August 2, 2006, 4:05:51 PM, you wrote:
(2) We're concerned about performance. Replacing GMP, but losing substantial performance on bignum-intensive programs would be unattractive.
don't forget about speed/memory efficiency of any programs that use Integer "just for case" but really most of their numbers fit in 32/64 bits. i have one particular program of this type - it builds list of all files on disk and Integers are used to save filesizes. i will be glad if, vice versa, memory requirements for small integers will be reduced to the same as for Ints
the same binary that also wants to use GMP. (Of course, we could *copy* GMP, changing all the function names. That would eliminate the problem!)
isn't it rather easy task for some automated tool? i think that even existing tools may be found -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

Hi Bulat,
don't forget about speed/memory efficiency of any programs that use Integer "just for case" but really most of their numbers fit in 32/64 bits. i have one particular program of this type - it builds list of all files on disk and Integers are used to save filesizes. i will be glad if, vice versa, memory requirements for small integers will be reduced to the same as for Ints
I was looking at this yesterday, partly because I read your previous discussion in "returning to cost of Integer." The low-level solution Lennart mentioned and that you noted is used in OCaml would be fast and convenient for a programmer. That solution would be much more difficult in C--, however, since it requires customisations for different processors or operating systems, especially 32 and 64bit architectures. Following the general trend of consensus, it should be part of the Bignum library; if the library does not have such a test it, as OpenSSL's BN library does not, it would have to be added. (With unmodified OpenSSL, you would have to examine the When the Bignum library returned the value to the RTS, the RTS would only have to check for the tag and store it accordingly.
the same binary that also wants to use GMP. (Of course, we could *copy* GMP, changing all the function names. That would eliminate the problem!)
isn't it rather easy task for some automated tool? i think that even existing tools may be found
I know copyrights are weak compared to patents but I do not think software copyrights are that weak. Just changing the names seems like a cosmetic change and performing the change through an automated system, doubly so. Copyrighted programs--particularly under the GPL license, which also covers the resulting object code--do not lose their copyright protection through name-mangling performed by a preprocessor. I think the lawyers for a company using GHC would probably be worried about it. Best Regards, Peter

Hello Peter, Wednesday, August 2, 2006, 10:37:23 PM, you wrote:
the same binary that also wants to use GMP. (Of course, we could *copy* GMP, changing all the function names. That would eliminate the problem!)
isn't it rather easy task for some automated tool? i think that even existing tools may be found
I know copyrights are weak compared to patents but I do not think
i proposed this is as solution for technical problem (inability to use GMP in ghc-compiled programs due to name reuse and inability to use ghc-specific GMP in user code), not as the way to avoid copyright problems :) -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

Hi Bulat,
the same binary that also wants to use GMP. (Of course, we could *copy* GMP, changing all the function names. That would eliminate the problem!)
isn't it rather easy task for some automated tool? i think that even existing tools may be found
I know copyrights are weak compared to patents but I do not think
i proposed this is as solution for technical problem (inability to use GMP in ghc-compiled programs due to name reuse and inability to use ghc-specific GMP in user code), not as the way to avoid copyright problems :)
Ahem... my apologies for taking it out of context. I took your comment (and Simon's) as copyright-related because I thought part of the problem with a single binary where foreign code used GHC's GMP was due to the integration of GMP's memory with the GHC RTS. Indeed it shouldn't be too difficult to change the names of the functions in GMP. -Peter

Simon,
(1) We'd be delighted to use a BSD-licensed alternative to GMP in GHC. It's been a long-standing issue, just never quite important enough to get done. If either or both of you are willing to put in the legwork, and emerge with an implementation that we understand and can maintain, we'd be happy to use it. We'll certainly help in any way we can.
I shouldn't speak for Esa, who kindly offered advice if I run into trouble. More than a few people seem interested in this, so maybe it will be a bunch of use can carry it off.
(2) We're concerned about performance. Replacing GMP, but losing substantial performance on bignum-intensive programs would be unattractive.
Definitely. You had mentioned OpenSSL as a possible replacement (at least it contains all the currently implemented Prelude functions over Integer except for lcm and integral powers). I had mentioned ARPREC and Esa had cautioned against attempting to integrate with a C+ + library. LibToMath covers everything and Esa had worked on that before. Would you be able to suggest another possibility?
(3) It's unlikely (albeit not impossible) that we'll get GMP-level performance out of a Haskell-only bignum library. ... this would be a step backwards!
It certainly would. As noted below I have been searching for high performance options because a Bignum library for a builtin-type such as Integer should optimally perform like an embedded system.
(4) The tricky spot for any library is memory allocation. Our GMP- based implementation works by getting GMP to use GHC's allocator to allocate memory. This means that every bignum is allocated in the Haskell heap, is automatically managed by GHC's garbage collector, which is Very Good.
How would lib-based memory allocation affect concurrency and parallelism? I mentioned to Esa that the library should be threaded, not merely thread-safe or reentrant. (OpenSSL is reentrant, through the CTX system, I believe.)
But because the allocator is statically linked to GMP, you can only have one allocator, and that leads to difficulties if you have another bit of the same binary that also wants to use GMP.
That seems to be the second main reason to replace GMP. I could modify the Bignum library to be multi-threaded, with a separate thread system tied to RTS-memory. Would that be workable?
(Of course, we could *copy* GMP, changing all the function names. That would eliminate the problem!)
In an email I sent to Bulat Ziganshin, I noted that such a fix would be legally worrisome: it seems like a cosmetic change, like changing the titles of chapters in a book. At the least I think it would worry the lawyers of any company using GHC to produce commercial products.
I suppose that one alternative is to let the library use 'malloc', but make a foreign-pointer proxy for every bignum, which calls 'free' when the GHC garbage collector frees it. Not as efficient, though.
Esa and I had discussed the possibility of copying the value returned from the Bignum lib into the GHC system, which certainly would not be very memory efficient, but might be faster. Among other memory modifications, it might be a good idea to initialise the Bignum lib with the RTS and modify the lib with a memory cache or garbage collection system of its own.
(5) If you do go ahead, could you pls start a Wiki page on the GHC development Wiki (http://hackage.haskell.org/trac/ghc), where you document your thoughts, the evolving design etc? You might want to extract the core of this email thread to initialise the Wiki page.
I got the page started on a document here already. I will have the rest up very soon. On a related note, I am working through the Makefiles for the RTS; I could clean things up a bit while I am at it. One of the big goals seemed to be to move to Cabal--or was that just for the Haskell libraries? I had mentioned this to Esa: would you be interested in moving to a higher level configuration system for heterogeneous program parts, such as Bakefile or Scons? Bakefile, at least, would result in the current make-based install but would be more easily maintainable and would allow variations for different compilers. Best regards, Peter

On Wed, Aug 02, 2006 at 03:22:57PM -0400, Peter Tanski wrote:
I suppose that one alternative is to let the library use 'malloc', but make a foreign-pointer proxy for every bignum, which calls 'free' when the GHC garbage collector frees it. Not as efficient, though.
Esa and I had discussed the possibility of copying the value returned from the Bignum lib into the GHC system, which certainly would not be very memory efficient, but might be faster. Among other memory modifications, it might be a good idea to initialise the Bignum lib with the RTS and modify the lib with a memory cache or garbage collection system of its own.
I don't understand why this would be useful. Just use the standard FFI ForeignPtr mechanism and it takes care of garbage collection for you and doesn't have any issues with concurrency. This would also make the library fully portable to any haskell implementation with FFI support. John -- John Meacham - ⑆repetae.net⑆john⑈

On 8/3/06, John Meacham
On Wed, Aug 02, 2006 at 03:22:57PM -0400, Peter Tanski wrote:
Esa and I had discussed the possibility of copying the value returned from the Bignum lib into the GHC system, which certainly would not be very memory efficient, but might be faster. Among other memory modifications, it might be a good idea to initialise the Bignum lib with the RTS and modify the lib with a memory cache or garbage collection system of its own.
I don't understand why this would be useful. Just use the standard FFI ForeignPtr mechanism and it takes care of garbage collection for you and doesn't have any issues with concurrency. This would also make the library fully portable to any haskell implementation with FFI support.
There is atleast one imaginable situation where copying would be safer: Imagine using a library that changes GMP memory allocation routines on (user-called) initialisation. Integers allocated before library init would probably crash the system when their finalisers were giving free-calls bad addresses. Then there's minor optimisations - memory being only in haskell heap it can be compacted, no need to check or run finalisers. Whetever these give more than we lose...benchmarking is hard without competiting implementations. I am not arguing it's a good choice. But it is totally valid choice with some good points, and it is interesting idea. There's also more a possible drawback: It requires even more knowledge, or assurances, from inner workings of the library. Best regards, --Esa
participants (5)
-
Bulat Ziganshin
-
Esa Ilari Vuokko
-
John Meacham
-
Peter Tanski
-
Simon Peyton-Jones