Hi,

can anybody point me to tutorials, papers, etc, on how to properly
annotate strictness in Haskell code? I am concerned with the following
stupid piece of code that eats a lot of memory and takes an incredible
amount of time to produce some output. I hope somebody will help me in
finding what I am doing wrong.

        Juanjo

---
module Main where

import Array

produce :: Int -> Double -> Array Int Double
produce n x = array (1,n) [(i,x) | i <- [1..n]]

scprod :: Array Int Double -> Array Int Double -> Double
scprod a b =
        case (bounds a, bounds b) of
          ((1,i), (1,j)) ->
                foldl (+) start [a!(x) * b!(x) | x <- [2..i]]
                where start = a!(1) * b!(1)

main = print (show (scprod a a))
       where a = produce 1000000 1.0

-- 
Juan Jose Garcia Ripoll         www: http://www.arrakis.es/~worm
Univ. Castilla-La Mancha        job: [EMAIL PROTECTED]
ETSI. Industriales              home: [EMAIL PROTECTED]
Departamento de Matematicas
c/Camilo Jose Cela, 3, Ciudad Real 13071 Spain



Reply via email to