
Hi everyone, I write a program for fast online multiplication, this means, leading digits are computed first, so this program is able to handle real numbers. My program and Source-Code is available under http://www.romeinf04.de http://www.romeinf04.de but only with german comments, because this is my master thesis. Now the problem: My program computes using the schoenhage-strassen multiply-subroutine the output everytime only until the 32777th Digit, but then it holds without an error message. Windows Task manager tells me CPU Usage 100% and Memory Allocation is increasing. Profiling told me, the function Algorithm.resultOfMult is using this memory. To compute the 32777th digit, my program needs several digits of the input-numbers including the 32800th. I'm using GHC 6.6.1 with option -O2 to compile. Output is row-wise by an IO-function, calling itself recursively with updated parameters, hte output looks like: dig11 dig21 --> res1 dig12 dig22 --> res2 dig12 dig23 --> res3 . . . and so on If I use the Naive-Multiply-Subroutine, the problem occurs at the 16392th digit. A friend of mine compiled it under Linux and got: . . . 32779 : 1 1 ---32776--> 0 32780 : 1 0 ---32777--> -1 Main: Ix{Integer}.index: Index (32766) out of range ((0,32765)) If I convert every Integer into Int and use instead of the generic list functions the prelude-list functions, it works. I don't have any idea, where the problem might be... Greetings Roman Please excuse my english writing, I'm from Germany. -- View this message in context: http://www.nabble.com/Where%27s-the-problem---tf4022913.html#a11426358 Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

On Wed, Jul 04, 2007 at 07:30:55AM -0700, Rome wrote:
I write a program for fast online multiplication, this means, leading digits are computed first, so this program is able to handle real numbers.
My program and Source-Code is available under http://www.romeinf04.de http://www.romeinf04.de
but only with german comments, because this is my master thesis.
Now the problem: My program computes using the schoenhage-strassen multiply-subroutine the output everytime only until the 32777th Digit, but then it holds without an error message. Windows Task manager tells me CPU Usage 100% and Memory Allocation is increasing. Profiling told me, the function Algorithm.resultOfMult is using this memory. To compute the 32777th digit, my program needs several digits of the input-numbers including the 32800th. I'm using GHC 6.6.1 with option -O2 to compile.
Output is row-wise by an IO-function, calling itself recursively with updated parameters, hte output looks like:
dig11 dig21 --> res1 dig12 dig22 --> res2 dig12 dig23 --> res3 . . . and so on
If I use the Naive-Multiply-Subroutine, the problem occurs at the 16392th digit.
A friend of mine compiled it under Linux and got: . . . 32779 : 1 1 ---32776--> 0 32780 : 1 0 ---32777--> -1 Main: Ix{Integer}.index: Index (32766) out of range ((0,32765))
If I convert every Integer into Int and use instead of the generic list functions the prelude-list functions, it works. I don't have any idea, where the problem might be...
If you're using the standard Schoenhage-Strassen algorithm, you might try using (*) on Integer - it uses Schoenhage-Strassen internally and is already debugged. Stefan

On Wed, 4 Jul 2007, Rome wrote:
I write a program for fast online multiplication, this means, leading digits are computed first, so this program is able to handle real numbers.
My program and Source-Code is available under http://www.romeinf04.de http://www.romeinf04.de
but only with german comments, because this is my master thesis.
Now the problem: My program computes using the schoenhage-strassen multiply-subroutine the output everytime only until the 32777th Digit, but then it holds without an error message. Windows Task manager tells me CPU Usage 100% and Memory Allocation is increasing.
This sounds like an unresolvable data dependency. E.g. a digit depends via some other variables on its own value or it depends on an infinite number of other digits.
Profiling told me, the function Algorithm.resultOfMult is using this memory. To compute the 32777th digit, my program needs several digits of the input-numbers including the 32800th. I'm using GHC 6.6.1 with option -O2 to compile.
Output is row-wise by an IO-function, calling itself recursively with updated parameters, hte output looks like:
dig11 dig21 --> res1 dig12 dig22 --> res2 dig12 dig23 --> res3 . . . and so on
If I use the Naive-Multiply-Subroutine, the problem occurs at the 16392th digit.
A friend of mine compiled it under Linux and got: . . . 32779 : 1 1 ---32776--> 0 32780 : 1 0 ---32777--> -1 Main: Ix{Integer}.index: Index (32766) out of range ((0,32765))
If I convert every Integer into Int and use instead of the generic list functions the prelude-list functions, it works.
... and the result is right?
I don't have any idea, where the problem might be...
Stupid question: Did you pay enough attentation to carries? There might be an unresolvable dependency if you request a digit which depends on infinitely many carries from following digits. If you like to compare with other implementations of real numbers, see: http://www.haskell.org/haskellwiki/Applications_and_libraries/Mathematics#Re...

A friend of mine compiled it under Linux and got: . . . 32779 : 1 1 ---32776--> 0 32780 : 1 0 ---32777--> -1 Main: Ix{Integer}.index: Index (32766) out of range ((0,32765))
If I convert every Integer into Int and use instead of the generic list functions the prelude-list functions, it works.
--... and the result is right?
I don't have any idea, where the problem might be...
--Stupid question: Did you pay enough attentation to carries? There might be --an unresolvable dependency if you request a digit which depends on --infinitely many carries from following digits. Thx for your reply. The next output-digit depends on several digits of the input, which are determined by the rectangles defined in module /Schedule/. Every coordinate of a single rectangle is unique by definition. Because I use Signed-Digit-Representation, carries are only local in a single call of the multiplication -subroutine. Further my program is the implementation of an online-algorithm, leading digits are computed first, so an infinte number of carries shouldn't be the reason, I think. In my opinion there is something wrong with the use of Integer because of the Linux-error message. I can only verify the correctness of the result of the first 30 output-digits, and these are okay in both cases: Int and Integer. -- View this message in context: http://www.nabble.com/Where%27s-the-problem---tf4022913.html#a11435728 Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

On Wed, 4 Jul 2007, Rome wrote:
A friend of mine compiled it under Linux and got: . . . 32779 : 1 1 ---32776--> 0 32780 : 1 0 ---32777--> -1 Main: Ix{Integer}.index: Index (32766) out of range ((0,32765))
If I convert every Integer into Int and use instead of the generic list functions the prelude-list functions, it works.
--... and the result is right?
I don't have any idea, where the problem might be...
--Stupid question: Did you pay enough attentation to carries? There might be --an unresolvable dependency if you request a digit which depends on --infinitely many carries from following digits.
Thx for your reply.
You are probably aware of the common problems related to computation with real numbers, thus my replies below might not be of much help. I assume that your problem is specific to your code and the solution requires understanding your algorithm and your implementation, I didn't invested time in either of these, so far.
The next output-digit depends on several digits of the input, which are determined by the rectangles defined in module /Schedule/. Every coordinate of a single rectangle is unique by definition. Because I use Signed-Digit-Representation, carries are only local in a single call of the multiplication -subroutine.
If you add at least 100 numbers in base 10 computation, then two carry steps become necessary, both with signed and unsigned digits.
Further my program is the implementation of an online-algorithm, leading digits are computed first, so an infinte number of carries shouldn't be the reason, I think.
At some time, you have to apply carries, otherwise digits will get out of range. You might want to make perfect carries by processing the digit stream from the right to left - which is obviously impossible and you have to follow a different strategy.
In my opinion there is something wrong with the use of Integer because of the Linux-error message. I can only verify the correctness of the result of the first 30 output-digits, and these are okay in both cases: Int and Integer.
You can verify correctness for any multiplication by multiplying huge Integers.

Henning Thielemann wrote:
On Wed, 4 Jul 2007, Rome wrote:
A friend of mine compiled it under Linux and got: . . . 32779 : 1 1 ---32776--> 0 32780 : 1 0 ---32777--> -1 Main: Ix{Integer}.index: Index (32766) out of range ((0,32765))
If I convert every Integer into Int and use instead of the generic list functions the prelude-list functions, it works.
--... and the result is right?
I don't have any idea, where the problem might be...
--Stupid question: Did you pay enough attentation to carries? There might be --an unresolvable dependency if you request a digit which depends on --infinitely many carries from following digits.
Thx for your reply.
You are probably aware of the common problems related to computation with real numbers, thus my replies below might not be of much help. I assume that your problem is specific to your code and the solution requires understanding your algorithm and your implementation, I didn't invested time in either of these, so far.
The next output-digit depends on several digits of the input, which are determined by the rectangles defined in module /Schedule/. Every coordinate of a single rectangle is unique by definition. Because I use Signed-Digit-Representation, carries are only local in a single call of the multiplication -subroutine.
If you add at least 100 numbers in base 10 computation, then two carry steps become necessary, both with signed and unsigned digits.
Further my program is the implementation of an online-algorithm, leading digits are computed first, so an infinte number of carries shouldn't be the reason, I think.
At some time, you have to apply carries, otherwise digits will get out of range. You might want to make perfect carries by processing the digit stream from the right to left - which is obviously impossible and you have to follow a different strategy.
In my opinion there is something wrong with the use of Integer because of the Linux-error message. I can only verify the correctness of the result of the first 30 output-digits, and these are okay in both cases: Int and Integer.
You can verify correctness for any multiplication by multiplying huge Integers. _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Now I've tested whether a 40k-digit multiplication is correct by using the type Int and it is. Another interesting thing I've discovered is: Prelude> length [1..1000000] 1000000 Prelude> Data.List.genericLength [1..1000000] *** Exception: stack overflow Maybe there is something wrong with Integer ? -- View this message in context: http://www.nabble.com/Where%27s-the-problem---tf4022913.html#a11441600 Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

R> Another interesting thing I've discovered is: Prelude>> length [1..1000000] R> 1000000 Prelude>> Data.List.genericLength [1..1000000] R> *** Exception: stack overflow R> Maybe there is something wrong with Integer ? No, there is something wrong with genericLength: Prelude> Data.List.foldl (+) 0 $ map (const 1) [1..1000000] :: Int *** Exception: stack overflow Prelude> Data.List.foldl' (+) 0 $ map (const 1) [1..1000000] :: Integer 1000000

On Thu, Jul 05, 2007 at 10:49:17AM +0400, Miguel wrote:
R> Another interesting thing I've discovered is:
Prelude>> length [1..1000000] R> 1000000 Prelude>> Data.List.genericLength [1..1000000] R> *** Exception: stack overflow
R> Maybe there is something wrong with Integer ?
No, there is something wrong with genericLength:
Prelude> Data.List.foldl (+) 0 $ map (const 1) [1..1000000] :: Int *** Exception: stack overflow Prelude> Data.List.foldl' (+) 0 $ map (const 1) [1..1000000] :: Integer 1000000
From ghc/libraries/base/Data/List.hs: genericLength :: (Num i) => [b] -> i genericLength [] = 0 genericLength (_:l) = 1 + genericLength l So genericLength is lazily building up unevaluated (+) expressions and running out of stack space. Is there a good reason for genericLength to be lazy? Phil -- http://www.kantaka.co.uk/ .oOo. public key: http://www.kantaka.co.uk/gpg.txt

Philip Armstrong wrote:
genericLength :: (Num i) => [b] -> i genericLength [] = 0 genericLength (_:l) = 1 + genericLength l
So genericLength is lazily building up unevaluated (+) expressions and running out of stack space.
Is there a good reason for genericLength to be lazy?
Yes, since addition in i may well be lazy. data Nat = Zero | Succ Nat instance Num Nat where Zero + b = b (Succ a) + b = Succ (a + b) ... natLength :: [a] -> Nat natLength = genericLength Also, you can turn the foldr into a foldl' with a cleverly chosen data type like data Int' = I Int | Plus Int' Int' eval :: Int' -> Int eval = eval' 0 where eval' (I i) k = k + i eval' (Plus x y) k = eval' y $! eval' x k instance Num Int' where (+) = Plus ... or in its bare essence newtype DiffInt = DI { unDI :: Int -> Int } instance Num DiffInt where (+) f g k = DI $ unDI g $! unDI f k evalDI :: DiffInt -> Int evalDI f = unDI f 0 Regards, apfelmus
participants (6)
-
apfelmus
-
Henning Thielemann
-
Miguel
-
Philip Armstrong
-
Rome
-
Stefan O'Rear