memorize function with number parameterized types in GHC

Hi, everyone I'm recently trying to implement the Montgomery reduction algorithm[1] in Haskell, the code can be found on my Github page[2]. After doing some benchmark testing I found that the library works rather slow. With the help of `trace` function from Debug.Trace, I found that GHC is not magical enough to memorize values with the same type(well, it's actually dynamically generated number parameterized type). I used binary representation to handle all positive numbers in type system.
data One = One data D0 a = D0 a data D1 a = D1 a class PostiveN a where p2num :: (Num b, Bits b) => a -> b instance PostiveN One ... instance PostiveN a => PostiveN (D0 a) ... instance PostiveN a => PostiveN (D1 a) ...
Here is a function that will be called everytime by `(*)` in `Num` typeclass
montgKeys :: (PostiveN p, Integral a, Bits a) => p -> a
as you can imagine, I always pass (undefined :: p) as parameter to `montgKeys`, so if it's handled well, it should be memorized for future usage. But tracing shows that both `p2num` and `montgKeys` are evaluated every time being called. So my question is, how to force GHC memorizing this kind of functions? [1]: http://en.wikipedia.org/wiki/Montgomery_reduction [2]: https://github.com/bjin/montg-reduce Regards, Bin

On Sun, Nov 6, 2011 at 9:10 PM, Bin Jin
Hi, everyone
I'm recently trying to implement the Montgomery reduction algorithm[1] in Haskell, the code can be found on my Github page[2]. After doing some benchmark testing I found that the library works rather slow. With the help of `trace` function from Debug.Trace, I found that GHC is not magical enough to memorize values with the same type(well, it's actually dynamically generated number parameterized type).
I used binary representation to handle all positive numbers in type system.
data One = One data D0 a = D0 a data D1 a = D1 a class PostiveN a where p2num :: (Num b, Bits b) => a -> b instance PostiveN One ... instance PostiveN a => PostiveN (D0 a) ... instance PostiveN a => PostiveN (D1 a) ...
Here is a function that will be called everytime by `(*)` in `Num` typeclass
montgKeys :: (PostiveN p, Integral a, Bits a) => p -> a
as you can imagine, I always pass (undefined :: p) as parameter to `montgKeys`, so if it's handled well, it should be memorized for future usage. But tracing shows that both `p2num` and `montgKeys` are evaluated every time being called.
So my question is, how to force GHC memorizing this kind of functions?
[1]: http://en.wikipedia.org/wiki/Montgomery_reduction [2]: https://github.com/bjin/montg-reduce
Regards, Bin
GHC only memorizes data structures, but not functions. See [1]. [1] http://www.haskell.org/haskellwiki/Memoization -- Yucheng Zhang

Hi,
Since I actually didn't use the parameter in calculation, the return value
only depends on the type
of input, not the actually value. If it's impossible to cache the result,
is there another way to
memorize this "function" ?
On Sun, Nov 6, 2011 at 9:20 PM, Yucheng Zhang
Hi, everyone
I'm recently trying to implement the Montgomery reduction algorithm[1] in Haskell, the code can be found on my Github page[2]. After doing some benchmark testing I found that the library works rather slow. With the help of `trace` function from Debug.Trace, I found that GHC is not magical enough to memorize values with the same type(well, it's actually dynamically generated number
On Sun, Nov 6, 2011 at 9:10 PM, Bin Jin
wrote: parameterized type).
I used binary representation to handle all positive numbers in type system.
data One = One data D0 a = D0 a data D1 a = D1 a class PostiveN a where p2num :: (Num b, Bits b) => a -> b instance PostiveN One ... instance PostiveN a => PostiveN (D0 a) ... instance PostiveN a => PostiveN (D1 a) ...
Here is a function that will be called everytime by `(*)` in `Num` typeclass
montgKeys :: (PostiveN p, Integral a, Bits a) => p -> a
as you can imagine, I always pass (undefined :: p) as parameter to `montgKeys`, so if it's handled well, it should be memorized for future usage. But tracing shows that both `p2num` and `montgKeys` are evaluated every time being called.
So my question is, how to force GHC memorizing this kind of functions?
[1]: http://en.wikipedia.org/wiki/Montgomery_reduction [2]: https://github.com/bjin/montg-reduce
Regards, Bin
GHC only memorizes data structures, but not functions. See [1].
[1] http://www.haskell.org/haskellwiki/Memoization
-- Yucheng Zhang
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Sun, Nov 6, 2011 at 9:35 PM, Bin Jin
Hi, Since I actually didn't use the parameter in calculation, the return value only depends on the type of input, not the actually value. If it's impossible to cache the result, is there another way to memorize this "function" ?
Sorry, I haven't considered about 'number parameterized type' when I answered the question. However, you can still use a data structure like MemoTrie [1] to memorize the function. The memorization is trivial, since you can convert between the number-typed 'undefined' and 'Integer' with the functions 'p2num' and 'num2p' in your code. I've not tested, but this is an example using MemoTrie:
import Data.MemoTrie
memoMontgKeys :: (PostiveN p, Integral a, Bits a) => p -> a memoMontgKeys = memoMontgKeys' . p2num
memoMontgKeys' :: (Integral a) => Integer -> a memoMontgKeys' = memo (montgKeys . num2p)
On the other hand, I think GHC is not expected to do the memorization automatically. An arbitrary number can turn up as the argument type of 'montgKeys'. This is similar to a function with an Integer argument, which GHC does not memorize now. [1] http://hackage.haskell.org/package/MemoTrie Yucheng Zhang

Hi,
Then how about p2num, how to memorize this function.
Also I think it's okay to memorize this kind of function. The type system
ensure all calling of montgKeys have the same type, e.g., it's a pure
function without parameter, it's safe to memorize it since it didn't occupy
more memory than representing dynamic generated types.
On Nov 6, 2011 11:06 PM, "Yucheng Zhang"
On Sun, Nov 6, 2011 at 9:35 PM, Bin Jin
wrote: Hi, Since I actually didn't use the parameter in calculation, the return value only depends on the type of input, not the actually value. If it's impossible to cache the result, is there another way to memorize this "function" ?
Sorry, I haven't considered about 'number parameterized type' when I answered the question.
However, you can still use a data structure like MemoTrie [1] to memorize the function. The memorization is trivial, since you can convert between the number-typed 'undefined' and 'Integer' with the functions 'p2num' and 'num2p' in your code. I've not tested, but this is an example using MemoTrie:
import Data.MemoTrie
memoMontgKeys :: (PostiveN p, Integral a, Bits a) => p -> a memoMontgKeys = memoMontgKeys' . p2num
memoMontgKeys' :: (Integral a) => Integer -> a memoMontgKeys' = memo (montgKeys . num2p)
On the other hand, I think GHC is not expected to do the memorization automatically. An arbitrary number can turn up as the argument type of 'montgKeys'. This is similar to a function with an Integer argument, which GHC does not memorize now.
[1] http://hackage.haskell.org/package/MemoTrie
Yucheng Zhang

On Sun, Nov 6, 2011 at 10:31, Bin Jin
Then how about p2num, how to memorize this function.
Also I think it's okay to memorize this kind of function. The type system ensure all calling of montgKeys have the same type, e.g., it's a pure function without parameter, it's safe to memorize it since it didn't occupy more memory than representing dynamic generated types.
Did you read the wiki page you were pointed to? ghc never memoizes functions by itself; the page provides pointers to a number of ways that you can add memoization, along with pointers to discussion of why there is no automated memoization. http://haskell.org/haskellwiki/Memoization -- brandon s allbery allbery.b@gmail.com wandering unix systems administrator (available) (412) 475-9364 vm/sms

Yes, but I think it's not a funtion since the function didn't use the
parameter. So maybe there is a way to make memorizing possible.
Also p2num is a general function used in number parameterized types, so I
asked this question here.
On Nov 6, 2011 11:41 PM, "Brandon Allbery"
On Sun, Nov 6, 2011 at 10:31, Bin Jin
wrote: Then how about p2num, how to memorize this function.
Also I think it's okay to memorize this kind of function. The type system ensure all calling of montgKeys have the same type, e.g., it's a pure function without parameter, it's safe to memorize it since it didn't occupy more memory than representing dynamic generated types.
Did you read the wiki page you were pointed to? ghc never memoizes functions by itself; the page provides pointers to a number of ways that you can add memoization, along with pointers to discussion of why there is no automated memoization.
http://haskell.org/haskellwiki/Memoization
-- brandon s allbery allbery.b@gmail.com wandering unix systems administrator (available) (412) 475-9364 vm/sms

On 11/6/11 10:51 AM, Bin Jin wrote:
Yes, but I think it's not a funtion since the function didn't use the parameter. So maybe there is a way to make memorizing possible.
In general, if the argument is not used then \x -> E is equal to let e = E in \x -> e Which we can make strict by adding a bang-pattern or a seq let !e = E in \x -> e == let e = E in e `seq` \x -> e The strictness isn't always necessary, but it helps to ensure that GHC doesn't get rid of the let-binding which would take us back to the original (\x -> E). Now, if we use this as the definition of the function, it'll ensure that the computation of E is done as a CAF and hence is memoized (since laziness is call-by-name + memoization). This trick can be generalized to any function of which parts of it are constant in some subset of parameters. That is, if we have \x y z -> E (F (G H x) y) z then this can be converted into let !h = H in \x -> let !g = G h x in \y -> let !f = F g y in \z -> E f z Now, whenever we want to use this function we pass in as many arguments as we are holding fixed, and force the resulting function in order to memoize the initial computations. For example, if the above function is called foo, then we could use it like: forM xs $ \x -> do let !foo_x = foo x forM ys $ \y -> do let !foo_x_y = foo_x y forM zs $ \z -> do let !foo_x_y_z = foo_x_y z ... In this example we're performing loop invariant code motion, but doing so dynamically in order to maintain a separation between the definition of foo and its use. -- Live well, ~wren

Hi
This method is what I'm looking for. it's a nice general solution, but it
doesn't solve my problem here.
I'm using ghc 7.0.3, I tried to cache p2num and montgKeys in the way you
showed. It seems that ghc doesn't memorize p2num and reject to compile new
montgKeys.
I think caching values with dynamic types is complicated in ghc's runtime
environment. Anyone knows the details?
On Nov 7, 2011 7:07 AM, "wren ng thornton"
On 11/6/11 10:51 AM, Bin Jin wrote:
Yes, but I think it's not a funtion since the function didn't use the parameter. So maybe there is a way to make memorizing possible.
In general, if the argument is not used then
\x -> E
is equal to
let e = E in \x -> e
Which we can make strict by adding a bang-pattern or a seq
let !e = E in \x -> e == let e = E in e `seq` \x -> e
The strictness isn't always necessary, but it helps to ensure that GHC doesn't get rid of the let-binding which would take us back to the original (\x -> E). Now, if we use this as the definition of the function, it'll ensure that the computation of E is done as a CAF and hence is memoized (since laziness is call-by-name + memoization).
This trick can be generalized to any function of which parts of it are constant in some subset of parameters. That is, if we have
\x y z -> E (F (G H x) y) z
then this can be converted into
let !h = H in \x -> let !g = G h x in \y -> let !f = F g y in \z -> E f z
Now, whenever we want to use this function we pass in as many arguments as we are holding fixed, and force the resulting function in order to memoize the initial computations. For example, if the above function is called foo, then we could use it like:
forM xs $ \x -> do let !foo_x = foo x forM ys $ \y -> do let !foo_x_y = foo_x y forM zs $ \z -> do let !foo_x_y_z = foo_x_y z ...
In this example we're performing loop invariant code motion, but doing so dynamically in order to maintain a separation between the definition of foo and its use.
-- Live well, ~wren
______________________________**_________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/**mailman/listinfo/haskell-cafehttp://www.haskell.org/mailman/listinfo/haskell-cafe

On Mon, Nov 7, 2011 at 9:29 AM, Bin Jin
Hi This method is what I'm looking for. it's a nice general solution, but it doesn't solve my problem here. I'm using ghc 7.0.3, I tried to cache p2num and montgKeys in the way you showed. It seems that ghc doesn't memorize p2num and reject to compile new montgKeys. I think caching values with dynamic types is complicated in ghc's runtime environment. Anyone knows the details?
Adding memorization directly to 'montgKeys' or 'p2num' should be possible, if you write your own version of MemoTrie dealing with dynamic types. However, this memorization requires an O(log P) lookup in the trie. This lookup process will require the whole type structure of P to be examined, which is of size O(log P). Yucheng Zhang

The actual time to calculate p2num and montgKeys are both O(log P). What
I'm looking is a constant time lookup.
On Nov 7, 2011 1:51 PM, "Yucheng Zhang"
On Mon, Nov 7, 2011 at 9:29 AM, Bin Jin
wrote: Hi This method is what I'm looking for. it's a nice general solution, but it doesn't solve my problem here. I'm using ghc 7.0.3, I tried to cache p2num and montgKeys in the way you showed. It seems that ghc doesn't memorize p2num and reject to compile new montgKeys. I think caching values with dynamic types is complicated in ghc's runtime environment. Anyone knows the details?
Adding memorization directly to 'montgKeys' or 'p2num' should be possible, if you write your own version of MemoTrie dealing with dynamic types.
However, this memorization requires an O(log P) lookup in the trie. This lookup process will require the whole type structure of P to be examined, which is of size O(log P).
Yucheng Zhang

On 7 November 2011 16:54, Bin Jin
The actual time to calculate p2num and montgKeys are both O(log P). What I'm looking is a constant time lookup.
Are these two functions CPU bottlenecks as revealed by profiling? If not, then you're probably over-optimising. Note that if O(1) lookup is really required, then that implies you use a static array, which requires you to pre-populate such an array with all possible values. -- Ivan Lazar Miljenovic Ivan.Miljenovic@gmail.com IvanMiljenovic.wordpress.com

It's all on these two functions. Three most frequently used operations of
Num (ModP x) are (+) (-) (*),each of them will at least call p2num once(to
get the modulus), in addition multiplication will call montgKeys. usual
implementation do both in constant time: p2num is written as number literal
with type "Integral a=>a", so a reasonable implementation should handle
these two function in constant time(in amortized time, of course).
On Nov 7, 2011 2:27 PM, "Ivan Lazar Miljenovic"
On 7 November 2011 16:54, Bin Jin
wrote: The actual time to calculate p2num and montgKeys are both O(log P). What I'm looking is a constant time lookup.
Are these two functions CPU bottlenecks as revealed by profiling? If not, then you're probably over-optimising.
Note that if O(1) lookup is really required, then that implies you use a static array, which requires you to pre-populate such an array with all possible values.
-- Ivan Lazar Miljenovic Ivan.Miljenovic@gmail.com IvanMiljenovic.wordpress.com

What's the purpose of all the type trickery? Why not just implement the algorithm using Integer?

In order to represent Z/nZ, regular way need to store two integers, and a
data constructer. With number parameterized types, newtype+Integer can be
used, it's much more efficient.
For this project, montg reduce require to calculate a key for each modulus,
but the modulus won't be changed within Num typeclass. It's better to fix
it in type system.
On Nov 7, 2011 1:38 AM, "DavidA"
What's the purpose of all the type trickery? Why not just implement the algorithm using Integer?
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
participants (6)
-
Bin Jin
-
Brandon Allbery
-
DavidA
-
Ivan Lazar Miljenovic
-
wren ng thornton
-
Yucheng Zhang