Calling a foreign function: superlinear comlexity

I call GSL's gsl_ran_ugaussian function in the following way (using bindings-gsl): module Main where import Bindings.Gsl.RandomNumberGeneration import Bindings.Gsl.RandomNumberDistributions import Foreign import Control.Monad import Data.List main = do let n = 100000 p <- peek p'gsl_rng_mt19937 rng <- c'gsl_rng_alloc p lst <- replicateM n $ c'gsl_rng_uniform rng print $ sum lst As I increase n from 10^4 to 10^5 to 10^6 execution time grows superlinearly. To forestall the answer that the reason is the overhead of List, this code scales approximately linearly: module Main where import Foreign import Control.Monad import Data.List main = do let n = 100000 let lst = map sin [1..n] print $ sum lst Another interesting observation: when I wrap the sin function of math.h with signature CDouble -> IO CDouble calling it repeatedly scales superlinearly, whereas when I wrap it as a pure function calling it repeatedly scales linearly. What is the reason for this performance and how can I make the first code scale linearly in execution time?

The problem isn't the list or the library library. It is the use of
the function sum, which is lazy and when you try to sum a very large
list, it makes a thunk for every single element in the list before
finally evaluating them all backwards to get the sum.
main = do
let n = 40000000
let lst = map sin [1..n]
print $ sum' lst
where
sum' = foldl1' (+)
This is linear, repeatable and quite a bit faster.
On Sun, Apr 10, 2011 at 7:26 PM, Serguei Son
I call GSL's gsl_ran_ugaussian function in the following way (using bindings-gsl):
module Main where
import Bindings.Gsl.RandomNumberGeneration import Bindings.Gsl.RandomNumberDistributions import Foreign import Control.Monad import Data.List
main = do let n = 100000 p <- peek p'gsl_rng_mt19937 rng <- c'gsl_rng_alloc p lst <- replicateM n $ c'gsl_rng_uniform rng print $ sum lst
As I increase n from 10^4 to 10^5 to 10^6 execution time grows superlinearly.
To forestall the answer that the reason is the overhead of List, this code scales approximately linearly:
module Main where
import Foreign import Control.Monad import Data.List
main = do let n = 100000 let lst = map sin [1..n] print $ sum lst
Another interesting observation: when I wrap the sin function of math.h with signature CDouble -> IO CDouble calling it repeatedly scales superlinearly, whereas when I wrap it as a pure function calling it repeatedly scales linearly.
What is the reason for this performance and how can I make the first code scale linearly in execution time?
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

Tried using foldl' (+) instead of sum, unfortunately it has not made the comlexity linear.

On Sun, Apr 10, 2011 at 6:26 PM, Serguei Son
I call GSL's gsl_ran_ugaussian function in the following way (using bindings-gsl):
module Main where
import Bindings.Gsl.RandomNumberGeneration import Bindings.Gsl.RandomNumberDistributions import Foreign import Control.Monad import Data.List
main = do let n = 100000 p <- peek p'gsl_rng_mt19937 rng <- c'gsl_rng_alloc p lst <- replicateM n $ c'gsl_rng_uniform rng print $ sum lst
As I increase n from 10^4 to 10^5 to 10^6 execution time grows superlinearly.
Not sure if it is related, but this thread also documents issues folks had with replicateM and performance: http://www.haskell.org/pipermail/haskell-cafe/2011-March/090419.html Antoine
To forestall the answer that the reason is the overhead of List, this code scales approximately linearly:
module Main where
import Foreign import Control.Monad import Data.List
main = do let n = 100000 let lst = map sin [1..n] print $ sum lst
Another interesting observation: when I wrap the sin function of math.h with signature CDouble -> IO CDouble calling it repeatedly scales superlinearly, whereas when I wrap it as a pure function calling it repeatedly scales linearly.
What is the reason for this performance and how can I make the first code scale linearly in execution time?
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

I suspect you want something a little more clever. In particular, because replicateM uses sequence under the hood, which is quite strict: it requires all of the IO actions to be evaluated before evaluation continues, so you end up with a big list built up in memory before it gets summed by 'sum'. I suspect if you run it manually with something like this you might do better: let loop 0 s = return s loop n s = do x <- c'gsl_rng_uniform rng loop (n-1) (s+x) print =<< loop n 0 With an actually pure function, you can do it more nicely, but it's a bit more fragile that way. Lazy IO would be another mechanism, although some people regard that to be a bit evil (and you'd still need to write the lazy IO equivalent of sequence). Edward Excerpts from Serguei Son's message of Sun Apr 10 19:26:16 -0400 2011:
I call GSL's gsl_ran_ugaussian function in the following way (using bindings-gsl):
module Main where
import Bindings.Gsl.RandomNumberGeneration import Bindings.Gsl.RandomNumberDistributions import Foreign import Control.Monad import Data.List
main = do let n = 100000 p <- peek p'gsl_rng_mt19937 rng <- c'gsl_rng_alloc p lst <- replicateM n $ c'gsl_rng_uniform rng print $ sum lst
As I increase n from 10^4 to 10^5 to 10^6 execution time grows superlinearly.
To forestall the answer that the reason is the overhead of List, this code scales approximately linearly:
module Main where
import Foreign import Control.Monad import Data.List
main = do let n = 100000 let lst = map sin [1..n] print $ sum lst
Another interesting observation: when I wrap the sin function of math.h with signature CDouble -> IO CDouble calling it repeatedly scales superlinearly, whereas when I wrap it as a pure function calling it repeatedly scales linearly.
What is the reason for this performance and how can I make the first code scale linearly in execution time?

On Sat, Apr 16, 2011 at 8:05 PM, Edward Z. Yang
I suspect you want something a little more clever. In particular, because replicateM uses sequence under the hood, which is quite strict: it requires all of the IO actions to be evaluated before evaluation continues, so you end up with a big list built up in memory before it gets summed by 'sum'. I suspect if you run it manually with something like this you might do better:
let loop 0 s = return s loop n s = do x <- c'gsl_rng_uniform rng loop (n-1) (s+x) print =<< loop n 0
With an actually pure function, you can do it more nicely, but it's a bit more fragile that way. Lazy IO would be another mechanism, although some people regard that to be a bit evil (and you'd still need to write the lazy IO equivalent of sequence).
You may use an iteratee for the same purpose. Using John Millikin's enumerator package, you can separate the function that calls the C code in an enumerator import qualified Data.Enumerator as E enumerator :: Integer -> E.Enumerator Double IO b enumerator n = E.replicateM n c'gsl_mg_uniform and the code that sums the values in an iteratee iteratee :: Monad m => E.Iteratee m Double iteratee = E.foldl' (+) 0 Calling them is as simple as E.run $ enumerator n $$ iteratee but note that you can also test your iteratee (which may be more complex than just summing) on any monad, including Identity. But unfortunately I don't think GHC (at least 6.12) can transform this code into something tidy as Edward's code. =( Cheers! =) -- Felipe.
participants (5)
-
Antoine Latter
-
David McBride
-
Edward Z. Yang
-
Felipe Almeida Lessa
-
Serguei Son